home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Language/OS - Multiplatform Resource Library
/
LANGUAGE OS.iso
/
oper_sys
/
emerald
/
emrldsys.lha
/
Language
/
Compiler
/
gencode.c
< prev
next >
Wrap
C/C++ Source or Header
|
1990-08-16
|
91KB
|
3,070 lines
/*
* @(#)gencode.c 1.16 2/23/90
*/
#include <sys/types.h>
#include <sys/stat.h>
#include <errno.h>
#include "assert.h"
#include "addresses.h"
#include "nodes.h"
#include "map.h"
#include "sequence.h"
#include "system.h"
#include "semantics.h"
#include "builtins.h"
#include "evaluate.h"
#include "opNames.h"
#include "primitives.h"
#include "allocate.h"
#include "MyParser.h"
#include "datadesc.h"
#include "environment.h"
#include "regdefs.h"
#include "genutils.h"
#include "emit.h"
#include "error.h"
#include "consts.h"
#include "flags.h"
#include "trace.h"
#include "option.h"
#include "ecTypes.h"
/*
* Imported routines
*/
extern void moveDataToRegister(), moveVariableToRegisters(), claimReg();
extern void resolveGlobal();
extern char *showInvoc(), *showExpression();
extern void doPrimitive();
extern Boolean isARealImport();
extern NodePtr tryToExecuteAsAT();
/*
* Global variables
*/
extern Map manifestMap;
extern int opNumber;
/*
* Exported definitions
*/
int nextLabelNumber = 101;
int currentInstruction;
OID currentCodeOID;
int nextOperationNumber = 0;
int nextObjectNumber = 0;
NodePtr currentObject = NULL, thisBuiltin = NULL;
/* measurement stuff */
int cEM_directCreates = 0;
int cEM_totalInvokes = 0;
int cEM_directInvokes = 0;
int cEM_inlinedInvokes = 0;
int cEM_localInvokes = 0;
int cEM_selfInvokes = 0;
int cEM_KCTimmutableInvokes = 0;
int cEM_UKCTimmutableInvokes = 0;
int cEM_KCTresidentGlobalInvokes = 0;
int cEM_UKCTresidentGlobalInvokes = 0;
int cEM_moves = 0;
int cEM_fixes = 0;
int cEM_unfixes = 0;
int cEM_refixes = 0;
int cEM_locates = 0;
int cEM_callByMoves = 0;
int cEM_callByVisits = 0;
int cEM_callByResultMoves = 0;
/*
* Local definitions
*/
#define USINGCONTINUE 1
static Map ocMap;
typedef enum { OC_Scheduled, OC_InProgress, OC_Done } OC_Stage;
static NodePtr ocStack;
static Boolean inObject = FALSE;
static Boolean inMonitor = FALSE;
static int nResultMoves = 0;
/*
* Forward definitions
*/
void generatePrimitive(), generateInvocation();
void generateExpression(), generateExp(), generateUnaryExp();
void generate(), generateTemplate(), generateVectorLiteral();
void generateKnownConcreteTypeInvoke();
void generateGlobalInvoke();
void generateImmutableGlobalInvoke();
void generateSelfInvoke();
void generateMonInit();
void generateMonEntry();
void generateMonExit();
void generateEnterOperation();
void generateReturn();
void generateCallC();
void incMoveAndVisit();
void generateMoveAndVisitMasks();
void generateAssign();
void generateAssignStat();
void generateInitially();
void generateProcess();
void generateRecovery();
void generateTemplate();
void generateATObject();
void generateCodeObject();
void generateResultAbCons();
void generateOneView();
void generateArgumentViews();
void ensureGenerate();
void generateLocationRequest();
void generate();
void generateCode();
DD generateCreation();
static Boolean isMyAddress();
Boolean isATrivialLiteral();
void generateInvocation(p, numResults, c)
NodePtr p;
int numResults;
Context c;
{
Variable *target;
Variable result;
int theOpNumber;
register NodePtr q, theObject;
register int i, nargs;
register NodePtr r, primno, opdef;
int opDefOpNumber, moveMask = 0, visitMask = 0;
NodePtr resultParam;
Symbol st;
NodePtr a, left, right;
assert(p->tag == P_INVOC);
q = (NodePtr) Map_Lookup(manifestMap, (int) p);
if ((int) q != NIL) {
assert(numResults == 1);
q = (NodePtr) Map_Lookup(manifestMap, (int)p+1);
assert((int)q != NIL);
q = (NodePtr) Map_Lookup(manifestMap, (int)p+2);
assert((int)q != NIL);
assert(q->tag == P_OBLIT || q->tag == P_ATLIT);
assert(q->b.oblit.f.writeSeparately);
if (q->tag == P_OBLIT) {
result.abCon = buildAbConFromObject(q);
result.data.kind = DD_OIDToODP;
result.data.value.id = q->b.oblit.id;
} else {
result.abCon = buildConCon(SIGNATUREINDEX);
result.data.kind = DD_OIDToODP;
result.data.value.id = q->b.atlit.id;
}
vPush(result);
return;
}
INCC(cEM_totalInvokes);
TS_StartInvocation();
generateExpression(p->b.invoc.target, anyContext);
target = vPeek(0);
if (isMyAddress(target->data)) {
q = currentObject;
} else {
q = getBestInfoFromAbCon(target->abCon);
}
theOpNumber = p->b.invoc.opNumber;
if (q->tag == P_OBLIT) {
/*
* We actually know the "concrete type" of this reference, so we can
* optimize this invocation.
*/
opdef = findObjectOperation(q, p->b.invoc.opname);
assert(opdef != NN);
assert(opdef->tag == P_OPDEF);
opDefOpNumber = opdef->b.opdef.opNumber;
# define isGuaranteedLocal(p, q) \
((OPTION(locals, 1) && (p->b.invoc.isLocal)) || \
(q)->b.oblit.f.immutable || \
(q) == currentObject)
if (isGuaranteedLocal(p, q) && opdef->b.opdef.isInlineable) {
/*
* We inline the operation, and do either a primitive or an object
* creation, or if option(inline) then we try an assignment.
*/
INCC(cEM_inlinedInvokes);
r = opdef->b.opdef.body;
assert(r->tag == P_BLOCK);
r = r->b.block.stats;
assert(isASequence(r));
assert(r->nChildren == 1);
ensureGenerate(q->b.oblit.codeOID);
if (r->b.children[0]->tag == P_PRIMSTAT) {
if (numResults == 1) {
resultParam = opdef->b.opdef.sig->b.opsig.results->b.children[0];
assert(resultParam->tag == P_PARAM);
st = resultParam->b.param.sym->b.symdef.symbol;
assert(st->tag == P_SYMBOL);
setDDAbstractType(c.v.abCon, getID(st->value.ATinfo));
}
primno = r->b.children[0]->b.primstat.number;
nargs = Sequence_Length(p->b.invoc.args);
assert (nargs <= 3);
if (nargs > 0) vForceToTemp(target, TS_PSL);
for (i = 0; i < nargs; i++) {
generateExpression(p->b.invoc.args->b.children[i], anyContext);
if (i < nargs - 1) vForceToTemp(vPeek(0), TS_PSL);
}
IFOPTION(comment, 2)
Comment("\t\t\t\tInlined primitive %s", primno->b.intlit.string);
doPrimitive(q, p, primno, target, nargs,
(Boolean) (numResults == 1), c);
} else {
assert(r->b.children[0]->tag == P_ASSIGNSTAT);
theObject = r->b.children[0]->b.assignstat.right->b.children[0];
if (theObject->tag == P_OBLIT) {
/*
* We know that we can inline this operation, so we know that the
* initially of the object expects the same parameters and returns
* exactly one result, just like this operation. We push the
* parameters onto the stack, and then do the object creation.
*/
IFOPTION(comment, 1) Comment("\t\t\t\tInlined create operation (%s)",
OPTION(locals, 1) && p->b.invoc.isLocal ? "local" : "global");
assert(numResults == 1);
result.abCon = buildAbConFromObject(theObject);
/* allocate space for the result before the arguments */
IFOPTION(createonstack, 1 &&
theObject->b.oblit.codeOID != OIDOfBuiltin(B_INSTCT, STRINGINDEX)) {
emitMove(result.abCon, pusher, 'l');
emitMove(nilDD, pusher, 'l');
}
if (!(theObject->b.oblit.f.isVector ||
theObject->b.oblit.codeOID == OIDOfBuiltin(B_INSTCT, BITCHUNKINDEX) ||
theObject->b.oblit.codeOID == OIDOfBuiltin(B_INSTCT, STRINGINDEX))) {
for (i = 0; i < Sequence_Length(p->b.invoc.args); i++) {
vPush(pusherContext.v);
generateExpression(p->b.invoc.args->b.children[i], pusherContext);
vGenerateAssign();
TS_Push();
}
} else {
assert(Sequence_Length(p->b.invoc.args) == 1);
generateExpression(p->b.invoc.args->b.children[0], anyContext);
if (theObject->b.oblit.codeOID == OIDOfBuiltin(B_INSTCT, STRINGINDEX)) {
moveDataToRegister(vPeek(0), regs_arg1, DataBrand);
} else {
moveDataToRegister(vPeek(0), regs_arg2, DataBrand);
}
(void) vPop();
}
result.data = generateCreation(theObject, TRUE,
(Boolean)(OPTION(locals, 1) && p->b.invoc.isLocal));
vPush(result);
} else {
/* this is an assignment with a single left and right */
IFOPTION(inline, 1) {
/*
* What we need to do is translate the addresses, probably force
* self into a register so that we can take care of the
* addressing, and worry about monitor entry. If we discover
* that we cannot perform the invoke, then goto doItForReal.
*/
/*
* at this point, r is a pointer to the statements in the block
* of the operation definition.
*/
a = r->b.children[0];
assert(a->tag == P_ASSIGNSTAT);
assert(Sequence_Length(a->b.assignstat.left) == 1);
assert(Sequence_Length(a->b.assignstat.right) == 1);
left = a->b.assignstat.left->b.children[0];
right = a->b.assignstat.right->b.children[0];
assert(left->tag == P_SYMREF);
if (right->tag == P_SYMREF || isATrivialLiteral(right)) {
goto doItForReal;
} else {
goto doItForReal;
}
} else {
goto doItForReal;
}
}
}
vDiscardN(numResults); /* discard the target */
TS_EndInvocation();
return;
} else if (opDefOpNumber == -1) {
/* This is ownName */
vDiscard();
vPushOwnName(q);
return;
} else if (opDefOpNumber == -2) {
vDiscard();
vPushOwnType(q);
return;
}
}
doItForReal:
if (theOpNumber < 0) {
/* this is ownName or ownType */
preemptKernelRegisters();
claimReg(regs_arg1, 1, ODPBrand);
result.data = buildRegisterDD(regs_arg1);
emitMove(target->abCon, result.data, 'l');
switch (theOpNumber) {
case -1:
generateKernelCall("em_ownName");
result.abCon = buildAbCon(OIDOfBuiltin(B_INSTAT, STRINGINDEX),
OIDOfBuiltin(B_INSTCT, STRINGINDEX));
break;
case -2:
generateKernelCall("em_ownType");
result.abCon = buildAbCon(OIDOfBuiltin(B_INSTAT, ABSTRACTTYPEINDEX),
OIDOfBuiltin(B_INSTCT, SIGNATUREINDEX));
break;
default:
assert(FALSE);
break;
}
vDiscard();
vPush(result);
return;
}
generateMoveAndVisitMasks(p, &moveMask, &visitMask);
vForceToTemp(target, TS_Stack | TS_PSL);
/*
* We know the ct if q is an oblit, but we have to generate a normal
* invocation of some sort.
*/
/* Results */
for (i = 0; i < numResults; i++) {
ddGenerateAssign(pusher, pusher, nilDD, nilDD);
TS_Results(8);
}
for (i = 0; i < Sequence_Length(p->b.invoc.args); i++) {
vPush(pusherContext.v);
generateExpression(p->b.invoc.args->b.children[i], pusherContext);
vGenerateAssign();
TS_Push();
}
preemptKernelRegisters();
if (q->tag == P_ATLIT) {
assert(target->data.kind == DD_Address);
if (q->b.atlit.f.immutable) {
generateImmutableGlobalInvoke(p, target->data, target->abCon,
theOpNumber, moveMask, visitMask);
} else {
if (p->b.invoc.isLocal)
if (!doGenerateCode) WarningMessage(p, "Local bit set incorrectly");
generateGlobalInvoke(p, target->data, target->abCon, theOpNumber,
moveMask, visitMask);
}
} else if (isMyAddress(target->data)) {
/* This is an invocation on myself, optimize it. */
/*
* TODO: We need to find the right opnumber, since the one we have (from
* p->b.invoc.opNumber) is appropriate for some abstract type.
*/
TRACE1(atctsort, 3, "Trying to translate op %s",
ON_Name(p->b.invoc.opname->b.opname.id));
#ifdef TRASHOPNUMBERS
theOpNumber = translateATOpNumberToCTOpNumber(target->abCon, theOpNumber);
assert(bflag || theOpNumber == opDefOpNumber);
#endif
generateSelfInvoke(p, opDefOpNumber, moveMask, visitMask);
} else {
generateKnownConcreteTypeInvoke(p, q, target->data, target->abCon,
theOpNumber, p->b.invoc.opname, moveMask, visitMask, p->b.invoc.isLocal);
}
for(i = 0; i < numResults; i++) {
result.data = popper;
result.abCon = popper;
if (i == 0) setDDAbstractType(result.abCon, p->b.invoc.resultTypeOID);
vPush(result);
}
preemptKernelRegisters();
vDiscardN(numResults); /* discard the target */
TS_EndInvocation();
}
/*
* Generate code to branch to the label if the expression is the same as
* sense.
*/
void generateBranch(sense, label)
Boolean sense;
int label;
{
Variable *bool;
wroteCode = TRUE;
bool = vPeek(0);
vForceToTemp(bool, TS_Stack);
switch (bool->data.kind) {
case DD_Address:
emit("\ttstl\t%s\n", addressToString(bool->data.value.address));
if (sense) {
emit("\tj%s\tL_%d\n", JN(NEQ), label);
} else {
emit("\tj%s\tL_%d\n", JN(EQL), label);
}
break;
case DD_PSLCondition:
if (sense) {
emit("\t%sj%s\tL_%d\n", JF(bool->data.value.condition.isFloat),
JN(bool->data.value.condition.psl), label);
} else {
emit("\t%sj%s\tL_%d\n",
JF(bool->data.value.condition.isFloat),
JN(negatedConditions[(int)bool->data.value.condition.psl]),
label);
}
break;
case DD_Manifest:
if (bool->data.value.manifest == sense) {
emit("\tj%s\tL_%d\n", JN(ALWAYS), label);
} else {
/* generate nothing */
}
break;
default:
assert(FALSE);
break;
}
vDiscard();
}
void generateIfClause(p, endLabel, falseLabel)
NodePtr p;
int endLabel, falseLabel;
{
lineNumberComment(p);
assert(p->tag == P_IFCLAUSE);
generateExpression(p->b.ifclause.exp, pslContext);
generateBranch(FALSE, falseLabel);
debugScope(1);
generate(p->b.ifclause.stats);
debugScope(0);
if (endLabel != 0) emit("\tj%s\tL_%d\n", JN(ALWAYS), endLabel);
}
void initializeGenerate()
{
assert(sizeof(ODTag) == sizeof(int));
nilNode = Construct(P_NILLIT, 0);
nilDD.kind = DD_Manifest;
nilDD.value.manifest = 0x80000000;
nullDD = buildRegisterDD(500);
pusher = nullDD;
pusher.kind = DD_Address;
nullDD.value.address = nullAddress;
pusher.value.address.autoDecrement = TRUE;
pusher.value.address.base = Stack;
pusher.value.address.offset = 0;
popper = nullDD;
popper.kind = DD_Address;
nullDD.value.address = nullAddress;
popper.value.address.autoIncrement = TRUE;
popper.value.address.base = Stack;
popper.value.address.offset = 0;
anyContext.kind = C_Any;
anyContext.v.data = nullDD;
anyContext.v.abCon = nullDD;
pslContext.kind = C_PSL;
pslContext.v = anyContext.v;
pusherContext.kind = C_Variable;
pusherContext.v.data = pusher;
pusherContext.v.abCon = pusher;
ocMap = Map_Create();
ocStack = NULL;
}
DD generateCreation(p, inlined, islocal)
NodePtr p;
Boolean inlined, islocal;
{
DD resultData;
Variable nev, *numEntries = &nev, tcv, *tc = &tcv;
int elementTypeSize;
wroteCode = TRUE;
tc->data = nullDD;
tc->data.kind = DD_OIDToCodePtr;
tc->data.value.id = getCodeOID(p);
tc->abCon = buildAbConFromObject(p);
if (p->b.oblit.codeOID == OIDOfBuiltin(B_INSTCT, STRINGINDEX)) {
preemptReg(regs_scratch, 1);
preemptReg(regs_arg2, 2);
if (inlined) {
numEntries->data = buildRegisterDD(regs_arg1);
} else {
numEntries->data = buildAddressDD(regs_l, firstParameterOffset);
}
numEntries->abCon = buildConCon(INTEGERINDEX);
moveDataToRegister(numEntries, regs_arg1, DataBrand);
generateKernelCall("em_createString");
freeReg(regs_arg1, 1);
claimReg(regs_arg1, 1, ODPBrand);
resultData = buildRegisterDD(regs_arg1);
} else if (p->b.oblit.f.isVector) {
/*
* movl sizeInBytes, arg_2
* call em_globalCreateSized
*/
if (p->b.oblit.codeOID == OIDOfBuiltin(B_INSTCT, BITCHUNKINDEX) ||
p->b.oblit.codeOID == OIDOfBuiltin(B_INSTCT, STRINGINDEX)) {
elementTypeSize = 1;
} else {
elementTypeSize = getSymbolSize(getElementTypeSymbol(p));
}
IFOPTION(comment, 1)
Comment("\t\t\t\t%sVector create %d bytes/element",
p->b.oblit.f.immutable ? "Immutable " : "",
elementTypeSize);
if (elementTypeSize == 8) elementTypeSize = 3;
else if (elementTypeSize == 4) elementTypeSize = 2;
else if (elementTypeSize == 1) elementTypeSize = 0;
else assert(FALSE);
if (inlined) {
numEntries->data = buildRegisterDD(regs_arg2);
} else {
numEntries->data = buildAddressDD(regs_l, firstParameterOffset);
}
numEntries->abCon = buildConCon(INTEGERINDEX);
moveDataToRegister(numEntries, regs_arg2, DataBrand);
moveDataToRegister(tc, regs_arg1, ODPBrand);
preemptReg(regs_scratch, 1);
claimReg(regs_arg3, 1, DataBrand);
#ifdef vax
emit("\tsubl3\t$ 1,%s,%s\n", RN(regs_arg2), RN(regs_arg3));
#endif
#ifdef sun
emitMove(buildRegisterDDNC(regs_arg2), buildRegisterDDNC(regs_arg3), 'l');
emit("\tsubql\t#1,%s\n", RN(regs_arg3));
#endif
if (elementTypeSize != 0)
#ifdef vax
emit("\tashl\t$ %d,%s,%s\n", elementTypeSize, RN(regs_arg2), RN(regs_arg2));
#endif
#ifdef sun
emit("\tasll\t#%d,%s\n", elementTypeSize, RN(regs_arg2));
#endif
if (OPTION(locals, 1) && islocal) {
generateKernelCall("em_localCreateVector");
} else if (p->b.oblit.f.immutable) {
generateKernelCall("em_localCreateVector");
} else {
generateKernelCall("em_globalCreateVector");
}
FREEV(tc);
FREEV(numEntries);
freeReg(regs_arg3, 1);
claimReg(regs_arg1, 1, ODPBrand);
resultData = buildRegisterDD(regs_arg1);
IFOPTION(createonstack, 1) {
emitMove(popper, resultData, 'l');
emit(POPABCON);
}
} else if (p->b.oblit.f.immutable || (OPTION(locals, 1) && islocal)) {
/* call local create */
IFOPTION(comment, 1) Comment("\t\t\t\t%s create",
p->b.oblit.f.immutable ? "Immutable" : "Local mutable");
assert(!p->b.oblit.f.isVector);
moveDataToRegister(tc, regs_arg1, ODPBrand);
preemptReg(regs_scratch, 1);
preemptReg(regs_arg2, 2);
generateKernelCall("em_localCreate");
FREEV(tc);
claimReg(regs_arg1, 1, ODPBrand);
resultData = buildRegisterDD(regs_arg1);
IFOPTION(createonstack, 1) {
emitMove(popper, resultData, 'l');
emit(POPABCON);
}
} else {
IFOPTION(comment, 1) Comment("\t\t\t\tGlobal create");
moveDataToRegister(tc, regs_arg1, ODPBrand);
preemptReg(regs_scratch, 1);
preemptReg(regs_arg2, 2);
generateKernelCall("em_globalCreate");
FREEV(tc);
claimReg(regs_arg1, 1, ODPBrand);
resultData = buildRegisterDD(regs_arg1);
IFOPTION(createonstack, 1) {
emitMove(popper, resultData, 'l');
emit(POPABCON);
}
}
return(resultData);
}
#define doChildren(p) {\
Sequence_For(child, p)\
if (child != NULL) generate(child);\
Sequence_Next\
}
static Boolean isMyAddress(d)
DD d;
{
return(d.kind == DD_Self);
}
void generateKnownConcreteTypeInvoke(p, theCode,
target, targetAbCon, opNumber, opname, moveMask, visitMask, isLocal)
NodePtr p;
NodePtr theCode;
DD target, targetAbCon;
int opNumber;
NodePtr opname;
int moveMask, visitMask;
Boolean isLocal;
{
NodePtr theOpDef;
int opDefOpNumber;
wroteCode = TRUE;
theOpDef = findObjectOperation(theCode, opname);
assert(theOpDef->tag == P_OPDEF);
opDefOpNumber = theOpDef->b.opdef.opNumber;
assert(targetAbCon.kind == DD_AbCon);
if (opNumber != opDefOpNumber) {
TRACE3(atctsort, 1, "Invocation: %s, opNumber = %d, opDefOpNumber = %d",
showInvoc(p), opNumber, opDefOpNumber);
}
if (theCode->b.oblit.f.immutable) {
INC(cEM_KCTimmutableInvokes);
IFOPTION(comment, 1)
Comment("\t\t\t\tKCTimmutableInvoke (%s)", showInvoc(p));
incMoveAndVisit(moveMask, visitMask);
ddGenerateAssign(
pusher,
pusher,
buildRegisterDDNC(regs_g),
buildRegisterDDNC(regs_l));
emitMove(buildRegisterDDNC(regs_b), pusher, 'l');
/*
* Since this object is immutable, we can invoke it directly.
*/
emitMove(target, buildRegisterDDNC(regs_g), 'l');
JUMPDEBUG();
emitMove(buildRegisterDDNC(regs_sp), buildRegisterDDNC(regs_l), 'l');
currentInstruction = nextLabelNumber++;
emit("L_%d:\tj%s\t%s0xabcdef01\n", currentInstruction,
JN(SUBR), GLOBALVARINDICATOR);
JUMPCHECK();
if (targetAbCon.kind == DD_AbCon) {
assert(getDDConcreteType(targetAbCon) == theCode->b.oblit.codeOID);
}
ensureGenerate(theCode->b.oblit.codeOID);
saveRelocationInfo(currentInstruction, 2, AR_OpNumberToAddress,
theCode->b.oblit.codeOID, (OID)opDefOpNumber);
} else if (OPTION(locals, 1) && isLocal) {
INC(cEM_localInvokes);
IFOPTION(comment, 1)
Comment("\t\t\t\tlocalInvoke (%s)", showInvoc(p));
incMoveAndVisit(moveMask, visitMask);
ddGenerateAssign(
pusher,
pusher,
buildRegisterDDNC(regs_g),
buildRegisterDDNC(regs_l));
emitMove(buildRegisterDDNC(regs_b), pusher, 'l');
/*
* Since this object is guaranteed local, we can invoke it directly.
*/
emitMove(target, buildRegisterDDNC(regs_g), 'l');
if (gdflag) {
emitBranchOnBit(ODTag_global, 'c', regs_g, buildLabelDD(6));
emitMove(buildRegisterDDNC(regs_g), buildRegisterDDNC(regs_arg1), 'l');
emitMove(targetAbCon, buildRegisterDDNC(regs_arg2), 'l');
emitMove(nilDD, buildRegisterDDNC(regs_arg3), 'l');
emitMove(buildRegisterDDNC(regs_sp), buildRegisterDDNC(regs_l), 'l');
generateKernelCall("em_invokeAssumptionFailure");
emit("6:\n");
}
JUMPDEBUG();
emitMove(buildRegisterDDNC(regs_sp), buildRegisterDDNC(regs_l), 'l');
currentInstruction = nextLabelNumber++;
emit("L_%d:\tj%s\t%s0xabcdef01\n", currentInstruction,
JN(SUBR), GLOBALVARINDICATOR);
JUMPCHECK();
if (targetAbCon.kind == DD_AbCon) {
assert(getDDConcreteType(targetAbCon) == theCode->b.oblit.codeOID);
}
ensureGenerate(theCode->b.oblit.codeOID);
saveRelocationInfo(currentInstruction, 2, AR_OpNumberToAddress,
theCode->b.oblit.codeOID, (OID)opDefOpNumber);
} else {
IFOPTION(comment, 1) Comment("\t\t\t\tKCTresidentGlobalInvoke (%s)",
showInvoc(p));
/* I know the ct, so I know that it is not immutable and not direct */
incMoveAndVisit(moveMask, visitMask);
ddGenerateAssign(
pusher,
pusher,
buildRegisterDDNC(regs_g),
buildRegisterDDNC(regs_l));
emitMove(buildRegisterDDNC(regs_b), pusher, 'l');
emitMove(target, buildRegisterDDNC(regs_b), 'l');
if (gdflag) {
emitBranchOnBit(ODTag_global, 's', regs_b, buildLabelDD(6));
emitMove(nilDD, buildRegisterDDNC(regs_arg1), 'l');
emitMove(targetAbCon, buildRegisterDDNC(regs_arg2), 'l');
emitMove(buildRegisterDDNC(regs_b), buildRegisterDDNC(regs_arg3), 'l');
emitMove(buildRegisterDDNC(regs_sp), buildRegisterDDNC(regs_l), 'l');
generateKernelCall("em_invokeAssumptionFailure");
emit("6:\n");
}
emitBranchOnBit(ODTag_frozen, 'c', regs_b, buildLabelDD(1));
/*
* We have to use the opNumber, which is from the abstract type, even
* though if we find it local we will be invoking a different operation.
* This is because we know the concrete type, but if we invoke this
* through the kernel, it will be using the ab/con (really the con/con),
* which does not include operations that are not exported.
*/
emitMove(buildManifestDD(opNumber), buildRegisterDDNC(regs_arg1), 'l');
emitMove(targetAbCon, buildRegisterDDNC(regs_arg2), 'l');
emitMove(buildLabelDD(2), pusher, 'l');
JUMPDEBUG();
if (moveMask != 0 || visitMask != 0) {
ddGenerateAssign(pusher, pusher, buildManifestDD(visitMask),
buildManifestDD(moveMask));
emit("\tjmp\t%s_em_invokeWithMove\n", GLOBALVARINDICATOR);
} else {
emit("\tjmp\t%s_em_invoke\n", GLOBALVARINDICATOR);
}
emit("1:\n");
emitMove(buildAddressDD(regs_b, GOD_dataPtr), buildRegisterDDNC(regs_g), 'l');
JUMPDEBUG();
emitMove(buildRegisterDDNC(regs_sp), buildRegisterDDNC(regs_l), 'l');
INC(cEM_KCTresidentGlobalInvokes);
currentInstruction = nextLabelNumber++;
emit("L_%d:\tj%s\t%s0xabcdef01\n", currentInstruction, JN(SUBR), GLOBALVARINDICATOR);
if (targetAbCon.kind == DD_AbCon) {
assert(getDDConcreteType(targetAbCon) == theCode->b.oblit.codeOID);
}
saveRelocationInfo(currentInstruction, 2, AR_OpNumberToAddress,
theCode->b.oblit.codeOID, (OID)opDefOpNumber);
emit("2:\n");
JUMPCHECK();
}
}
void generateGlobalInvoke(p, target, targetAbCon, theOpNumber, moveMask,
visitMask)
NodePtr p;
DD target, targetAbCon;
int theOpNumber, moveMask, visitMask;
{
wroteCode = TRUE;
IFOPTION(comment, 1) Comment("\t\t\t\tUKCTresidentGlobalInvoke (%s)",
showInvoc(p));
incMoveAndVisit(moveMask, visitMask);
ddGenerateAssign(
pusher,
pusher,
buildRegisterDDNC(regs_g),
buildRegisterDDNC(regs_l));
emitMove(buildRegisterDDNC(regs_b), pusher, 'l');
emitMove(targetAbCon, buildRegisterDDNC(regs_scratch), 'l');
emitBranchOnBit(ODTag_frozen, 'c', regs_scratch, buildLabelDD(9));
emitMove(target, buildRegisterDDNC(regs_b), 'l');
if (gdflag) {
emitBranchOnBit(ODTag_global, 's', regs_b, buildLabelDD(6));
emitMove(nilDD, buildRegisterDDNC(regs_arg1), 'l');
emitMove(buildRegisterDDNC(regs_scratch), buildRegisterDDNC(regs_arg2), 'l');
emitMove(buildRegisterDDNC(regs_b), buildRegisterDDNC(regs_arg3), 'l');
emitMove(buildRegisterDDNC(regs_sp), buildRegisterDDNC(regs_l), 'l');
generateKernelCall("em_invokeAssumptionFailure");
emit("6:\n");
}
emitBranchOnBit(ODTag_frozen, 'c', regs_b, buildLabelDD(1));
emitMove(buildManifestDD(theOpNumber), buildRegisterDDNC(regs_arg1), 'l');
emitMove(buildRegisterDDNC(regs_scratch), buildRegisterDDNC(regs_arg2), 'l');
emitMove(buildLabelDD(2), pusher, 'l');
JUMPDEBUG();
if (moveMask != 0 || visitMask != 0) {
ddGenerateAssign(pusher, pusher, buildManifestDD(visitMask),
buildManifestDD(moveMask));
emit("\tjmp\t%s_em_invokeWithMove\n", GLOBALVARINDICATOR);
} else {
emit("\tjmp\t%s_em_invoke\n", GLOBALVARINDICATOR);
}
emit("9:\n");
emitMove(target, buildRegisterDDNC(regs_g), 'l');
emit("\tj%s\t5f\n", JN(ALWAYS));
emit("1:\n");
emitMove(buildAddressDD(regs_b, GOD_dataPtr), buildRegisterDDNC(regs_g), 'l');
emit("5:");
JUMPDEBUG();
emitMove(buildRegisterDDNC(regs_sp), buildRegisterDDNC(regs_l), 'l');
INC(cEM_UKCTresidentGlobalInvokes);
assert(theOpNumber >= 0);
#ifdef vax
emit("\tj%s\t* %d+%d(%s)\n", JN(SUBR), AbCon_opVector,
theOpNumber * sizeof_AbConOpVectorEntry, RN(regs_scratch));
#endif
#ifdef sun
emitMove(buildAddressDD(regs_scratch,
AbCon_opVector + theOpNumber * sizeof_AbConOpVectorEntry),
buildRegisterDDNC(regs_scratch), 'l');
emit("\tj%s\t%s@\n", JN(SUBR), RN(regs_scratch));
#endif
emit("2:\n");
JUMPCHECK();
}
void generateImmutableGlobalInvoke(p, target, targetAbCon, theOpNumber,
moveMask, visitMask)
NodePtr p;
DD target, targetAbCon;
int theOpNumber, moveMask, visitMask;
{
wroteCode = TRUE;
INC(cEM_UKCTimmutableInvokes);
IFOPTION(comment, 1) Comment("\t\t\t\tUKCTimmutableInvoke (%s)",
showInvoc(p));
incMoveAndVisit(moveMask, visitMask);
ddGenerateAssign(
pusher,
pusher,
buildRegisterDDNC(regs_g),
buildRegisterDDNC(regs_l));
emitMove(buildRegisterDDNC(regs_b), pusher, 'l');
emitMove(targetAbCon, buildRegisterDDNC(regs_scratch), 'l');
/*
* Since this object is immutable, we can invoke it directly.
*/
emitMove(target, buildRegisterDDNC(regs_g), 'l');
if (gdflag) {
emitBranchOnBit(ODTag_frozen, 'c', regs_scratch, buildLabelDD(6));
emitBranchOnBit(ODTag_replicated, 's', regs_g, buildLabelDD(6));
emitMove(buildRegisterDDNC(regs_g), buildRegisterDDNC(regs_arg1), 'l');
emitMove(buildRegisterDDNC(regs_scratch), buildRegisterDDNC(regs_arg2),
'l');
emitMove(nilDD, buildRegisterDDNC(regs_arg3), 'l');
emitMove(buildRegisterDDNC(regs_sp), buildRegisterDDNC(regs_l), 'l');
generateKernelCall("em_invokeAssumptionFailure");
emit("6:\n");
}
JUMPDEBUG();
emitMove(buildRegisterDDNC(regs_sp), buildRegisterDDNC(regs_l), 'l');
#ifdef vax
emit("\tj%s\t* %d+%d(%s)\n", JN(SUBR), AbCon_opVector,
theOpNumber * sizeof_AbConOpVectorEntry, RN(regs_scratch));
#endif
#ifdef sun
emitMove(buildAddressDD(regs_scratch,
AbCon_opVector + theOpNumber * sizeof_AbConOpVectorEntry),
buildRegisterDDNC(regs_scratch), 'l');
emit("\tj%s\t%s@\n", JN(SUBR), RN(regs_scratch));
#endif
JUMPCHECK();
}
/*ARGSUSED*/
void generateSelfInvoke(p, theOpNumber, moveMask, visitMask)
NodePtr p;
int theOpNumber, moveMask, visitMask;
{
wroteCode = TRUE;
INC(cEM_selfInvokes);
IFOPTION(comment, 1) Comment("\t\t\t\tselfInvoke (%s)", showInvoc(p));
incMoveAndVisit(moveMask, visitMask);
ddGenerateAssign(
pusher,
pusher,
buildRegisterDDNC(regs_g),
buildRegisterDDNC(regs_l));
emitMove(buildRegisterDDNC(regs_b), pusher, 'l');
JUMPDEBUG();
emitMove(buildRegisterDDNC(regs_sp), buildRegisterDDNC(regs_l), 'l');
emit("\tj%s\tL_operationEP_%d\n", JN(SUBR), theOpNumber);
JUMPCHECK();
}
void generateMonInit()
{
DD mon, zero;
int offset =
firstInstanceOffset+(currentObject->b.oblit.f.immutable ? 4 : 0);
assert(currentObject->b.oblit.monitor != NN);
if (currentObject->b.oblit.monitor->b.monitor.mayBeElided) return;
zero = buildManifestDD(0);
mon = buildAddressDD(regs_g, offset);
ddGenerateAssign(mon, nextAddress(mon), zero, zero);
}
void generateMonEntry()
{
int offset =
firstInstanceOffset+(currentObject->b.oblit.f.immutable ? 4 : 0);
assert(currentObject->b.oblit.monitor != NN);
if (currentObject->b.oblit.monitor->b.monitor.mayBeElided) return;
#ifdef vax
emit("\tbbcs\t$0,%d(%s),1f\n", offset, RN(regs_g));
#endif
#ifdef sun
emit("\tbset\t#0,%s@(%d)\n", RN(regs_g), offset + 3);
emit("\tb%s\t1f\n", JN(EQL));
#endif
emitMoveAddress(buildAddressDD(regs_g, offset),buildRegisterDDNC(regs_arg1));
generateKernelCall("em_monEntry");
emit("1:\n");
}
void generateMonExit()
{
int offset =
firstInstanceOffset+(currentObject->b.oblit.f.immutable ? 4 : 0);
assert(currentObject->b.oblit.monitor != NN);
if (currentObject->b.oblit.monitor->b.monitor.mayBeElided) return;
#define NEWVERSION
#ifdef NEWVERSION
emit("\ttstl\t");
writeDD(buildAddressDD(regs_g, offset + sizeof(int)), '\n');
emit("\tj%s\t1f\n", JN(EQL));
#endif
emitMoveAddress(buildAddressDD(regs_g, offset),buildRegisterDDNC(regs_arg1));
generateKernelCall("em_monExit");
#ifdef NEWVERSION
emit("\tj%s\t2f\n", JN(ALWAYS));
emit("1:");
emitMove(buildManifestDD(0), buildAddressDD(regs_g, offset), 'l');
emit("2:\n");
#endif
}
void generateEnterOperation(localSize, maxStack)
int localSize, maxStack;
{
IFOPTION(comment, 1)
Comment("\t\t\t\tEnterOperation(%d, %d)", localSize, maxStack);
emitMoveAddress(buildAddressDD(regs_sp, -maxStack),
buildRegisterDDNC(regs_scratch));
emit("\tcmpl\t%s_splimit,", GLOBALVARINDICATOR);
writeDD(buildRegisterDDNC(regs_scratch), '\n');
#ifdef vax
emit("\tb%s\t1f\n", JN(LEQU));
#endif
#ifdef sun
emit("\tb%s\t1f\n", JN(GTRU));
#endif
emitMove(buildManifestDD(maxStack), buildRegisterDDNC(regs_arg1), 'l');
generateKernelCall("em_stackCheck");
emit("1:\n");
emitMove(buildRegisterDDNC(regs_ssp), pusher, 'l');
localSize -= 4;
IFOPTION(nilspace, 1) {
if (localSize > 0) {
emitMove(nilDD, buildRegisterDDNC(regs_arg2), 'l');
emitMove(buildManifestDD((localSize/4) - 1), buildRegisterDDNC(regs_arg3), 'l');
emit("1:");
emitMove(buildRegisterDDNC(regs_arg2), pusher, 'l');
#ifdef vax
emit("\tsobgeq\t");
#endif
#ifdef sun
emit("\tdbf\t");
#endif
writeDD(buildRegisterDDNC(regs_arg3), ',');
writeLabel(buildLabelDD(-1), '\n');
}
} else IFOPTION(nilspace, 2) {
#ifdef vax
emit("\tsubl2\t$%d, sp\n", localSize);
#endif
#ifdef sun
emit("\taddw\t#%d, sp\n", -localSize);
#endif
} else assert(FALSE);
}
void generateReturn(paramBytes)
int paramBytes;
{
wroteCode = TRUE;
IFOPTION(comment, 1) Comment("\t\t\t\treturn(%d)", paramBytes);
IFOPTION(invokequeue, 1) {
emit("\ttstl\t");
writeDD(buildAddressDD(regs_l, -8), '\n');
emit("\tj%s\t1f\n", JN(GTR));
#ifdef vax
emit("\tremque\t-%d(%s),%s\n",
firstLocalOffset+sizeof(InvokeQueue), RN(regs_l), RN(regs_scratch));
#endif
#ifdef sun
{
DD F, B, T, O;
F = buildAddressDD(regs_l, -(firstLocalOffset + sizeof(InvokeQueue)));
B = nextAddress(F);
T = buildRegisterDDNC(regs_scratch);
emitMove(F, T, 'l');
O = buildAddressDD(regs_scratch, 4);
emitMove(B, O, 'l');
emitMove(B, T, 'l');
O = buildAddressDD(regs_scratch, 0);
emitMove(F, O, 'l');
}
#endif
emit("1:\n");
} else IFOPTION(invokequeue, 2) {
#ifdef vax
emit("\tremque\t-%d(%s),%s\n",
firstLocalOffset+sizeof(InvokeQueue), RN(regs_l), RN(regs_scratch));
#endif
#ifdef sun
Comment("Queue remove!!!!!");
#endif
} else {
assert(FALSE);
}
emitMoveAddress(buildAddressDD(regs_l, -4), buildRegisterDDNC(regs_sp));
emitMove(popper, buildRegisterDDNC(regs_scratch), 'l');
emitMove(popper, buildRegisterDDNC(regs_b), 'l');
ddGenerateAssign(
buildRegisterDDNC(regs_g),
buildRegisterDDNC(regs_l),
popper,
popper);
if (paramBytes != 0) {
#ifdef vax
emit("\taddl2\t");
#endif
#ifdef sun
emit("\tadd%sw\t", inRange(paramBytes, 0, 8) ? "q" : "");
#endif
writeDD(buildManifestDD(paramBytes), ',');
writeDD(buildRegisterDDNC(regs_sp), '\n');
}
if (gdflag) emit(SETLASTJUMPFROM);
emit("\tjmp\t");
writeDD(buildAddressDD(regs_scratch, 0), '\n');
}
void generateCallC(n, name, isExpression)
int n;
char *name;
Boolean isExpression;
{
DD mover;
int reg;
wroteCode = TRUE;
IFOPTION(comment, 1) Comment("\t\t\t\tCallC $%d,%s", n, name);
#ifdef sun
emitMove(buildRegisterDDNC(regs_ssp), buildRegisterDDNC(regs_scratch), 'l');
emitMoveAddress(buildAddressDD(regs_scratch, SS_regs),
buildRegisterDDNC(regs_scratch));
#endif
#ifdef vax
emitMoveAddress(buildAddressDD(regs_ssp, SS_regs),
buildRegisterDDNC(regs_scratch));
#endif
mover = popper;
mover.value.address.base = regs_scratch;
setDDAbstractType(mover, OIDOfBuiltin(B_INSTAT, INTEGERINDEX));
emitMove(buildRegisterDDNC(4), mover, 'l');
for (reg = 5; reg <= 14; reg += 2) {
ddGenerateAssign(
mover,
mover,
buildRegisterDDNC(reg),
buildRegisterDDNC(reg+1));
}
#ifdef OLDCPRIM
emit("\tmovl\t%s_kernelsp,sp\n", GLOBALVARINDICATOR);
if (n >= 3) emitMove(buildRegisterDDNC(regs_arg3), pusher, 'l');
if (n >= 2) emitMove(buildRegisterDDNC(regs_arg2), pusher, 'l');
if (n >= 1) emitMove(buildRegisterDDNC(regs_arg1), pusher, 'l');
#else
emit("\tmovl\t%s,sp\n", RN(regs_arg1));
#endif
#ifdef vax
emit("\tcalls\t$%d,*$ _%s\n", n, name);
#endif
#ifdef sun
emit("\tj%s\t_%s\n", JN(SUBR), name);
if (n > 0) emit("\tadd%sw\t#%d,sp\n", n <= 2 ? "q" : "", n * 4);
#endif
if (isExpression) {
emitMove(buildRegisterDDNC(regs_cresult),buildRegisterDDNC(regs_arg1),'l');
}
emit("\tmovl\t%s_currentSSP,%s\n", GLOBALVARINDICATOR, RN(regs_ssp));
#ifdef sun
emitMove(buildRegisterDDNC(regs_ssp), buildRegisterDDNC(regs_scratch), 'l');
emitMoveAddress(buildAddressDD(regs_scratch, SS_regs),
buildRegisterDDNC(regs_scratch));
#endif
#ifdef vax
emitMoveAddress(buildAddressDD(regs_ssp, SS_regs),
buildRegisterDDNC(regs_scratch));
#endif
emitMove(mover, buildRegisterDDNC(4), 'l');
for (reg = 5; reg <= 14; reg += 2) {
ddGenerateAssign(
buildRegisterDDNC(reg),
buildRegisterDDNC(reg+1),
mover,
mover);
}
}
void incMoveAndVisit(moveMask, visitMask)
int moveMask, visitMask;
{
register int i;
if (! (gmflag && doGenerateCode)) return;
for (i = 0; i < 32; i++) {
if (moveMask & (1 << i)) INC(cEM_callByMoves);
if (visitMask & (1 << i)) INC(cEM_callByVisits);
}
}
void generateMoveAndVisitMasks(p, moveMask, visitMask)
NodePtr p;
int *moveMask, *visitMask;
{
register NodePtr q, r;
*moveMask = 0;
*visitMask = 0;
assert(p->tag == P_INVOC);
q = p->b.invoc.args;
Sequence_For(r, q)
assert(r->tag == P_ARG);
if (z__z > 31) ErrorMessage(p, "Implementation restriction 32 arguments");
if (r->b.arg.move) (*moveMask) |= (1 << z__z);
if (r->b.arg.visit) (*visitMask) |= (1 << z__z);
Sequence_Next
}
Boolean isATrivialLiteral(p)
NodePtr p;
{
register Tag t = p->tag;
return(t == P_STRINGLIT ||
t == P_CHARLIT ||
t == P_INTLIT ||
t == P_REALLIT ||
t == P_BOOLLIT ||
t == P_NILLIT ||
t == P_BUILTINLIT);
}
void generateAssign(var, val)
NodePtr var, val;
{
register Symbol st;
Context c;
st = ST_Fetch(var->b.symref.symbol);
vPushVariable(st);
c.kind = C_Variable;
c.v = vTop();
generateExpression(val, c);
vGenerateAssign();
assert(vEmpty());
}
void doMultipleAssigns(p)
register NodePtr p;
{
register NodePtr q;
assert(isASequence(p));
Sequence_ReverseFor(q, p)
assert(q->tag == P_SYMREF);
vPushVariable(q->b.symref.symbol);
vSwap();
vGenerateAssign();
Sequence_Next
}
void generateAssignStat(p)
NodePtr p;
{
register NodePtr q;
Variable result;
OID id;
assert(p->tag == P_ASSIGNSTAT);
if (Sequence_Length(p->b.assignstat.left) == 0) {
assert(Sequence_Length(p->b.assignstat.right) == 1);
generateInvocation(p->b.assignstat.right->b.children[0], 0,
anyContext);
} else if (Sequence_Length(p->b.assignstat.right) == 1) {
/*
* We have either a simple assignment or a procedure call with multiple
* results.
*/
if (Sequence_Length(p->b.assignstat.left) == 1) {
/*
* Just a simple assignment.
*/
generateAssign(p->b.assignstat.left->b.children[0],
p->b.assignstat.right->b.children[0]);
} else {
/*
* A procedure call with multiple results.
*/
generateInvocation(p->b.assignstat.right->b.children[0],
Sequence_Length(p->b.assignstat.left), anyContext);
doMultipleAssigns(p->b.assignstat.left);
}
} else {
/*
* We have a multiple assignment statement.
*/
assert(Sequence_Length(p->b.assignstat.left) ==
Sequence_Length(p->b.assignstat.right));
result.data = popper;
result.abCon = popper;
Sequence_For(q, p->b.assignstat.right)
vPush(pusherContext.v);
generateExpression(q, pusherContext);
result.abCon = vTopAbCon();
vGenerateAssign();
id = getDDAbstractType(result.abCon);
result.abCon = popper;
setDDAbstractType(result.abCon, id);
vPush(result);
TS_Push();
Sequence_Next
doMultipleAssigns(p->b.assignstat.left);
}
}
/*
* hasInitially returns true iff generateInitially actually generates any
* code.
*/
extern Boolean isAManifestConstant();
static Boolean hasInitially(p)
NodePtr p;
{
register NodePtr q;
register Symbol st;
assert(p->tag == P_OBLIT);
if (p->b.oblit.monitor != NN) {
if (! p->b.oblit.monitor->b.monitor.mayBeElided) return(TRUE);
if (p->b.oblit.monitor->b.monitor.init != NN) return(TRUE);
}
Sequence_For(q, p->b.oblit.setq)
st = ST_Fetch(q->b.setq.inner->b.symref.symbol);
if (isARealImport(st, TRUE) && st->usedOutsideInitially) return(TRUE);
Sequence_Next
Sequence_For(q, p->b.oblit.decls)
if (q->tag == P_VARDECL) return(TRUE);
else if (q->tag == P_CONSTDECL) {
st = ST_Fetch(q->b.constdecl.sym->b.symdef.symbol);
if (! isAManifestConstant(st)) return(TRUE);
} else {
assert(FALSE);
}
Sequence_Next
if (p->b.oblit.monitor != NN) {
Sequence_For(q, p->b.oblit.monitor->b.monitor.decls)
if (q->tag == P_VARDECL) return(TRUE);
else if (q->tag == P_CONSTDECL) {
st = ST_Fetch(q->b.constdecl.sym->b.symdef.symbol);
if (! isAManifestConstant(st)) return(TRUE);
} else {
assert(FALSE);
}
Sequence_Next
}
if (getCodeOID(p) == OIDOfBuiltin(B_INSTCT, CONDITIONINDEX)) return(TRUE);
return(FALSE);
}
void generateInitially(p)
NodePtr p;
{
AllocationInfoPtr initaip;
assert(p->tag == P_OBLIT);
initaip = fetchAllocationInfo((NodePtr) ((int)p + 1));
initializeTemplate("L_initiallyTemplate", nextObjectNumber, TRUE);
generateTemplate(initaip);
emit("L_initiallyEP:\n");
lineNumberComment(p);
/*
* Generate the enter operation code.
*/
TS_startOperation(initaip, nextObjectNumber, 10001);
generate(p->b.oblit.setq);
generate(p->b.oblit.decls);
if (p->b.oblit.monitor != NN) {
/* initialize the monitor */
generateMonInit();
generate(p->b.oblit.monitor->b.monitor.decls);
generate(p->b.oblit.monitor->b.monitor.init);
}
if (getCodeOID(p) == OIDOfBuiltin(B_INSTCT, CONDITIONINDEX)) {
emitMove(buildRegisterDDNC(regs_b), buildRegisterDDNC(regs_arg1), 'l');
generateKernelCall("em_condInit");
}
TS_endOperation(FALSE, TRUE, FALSE);
freeAllRegs();
}
void generateProcess(p)
NodePtr p;
{
AllocationInfoPtr aip;
register NodePtr child;
if (p == NN) return;
assert(p->tag == P_PROCESSDEF || p->tag == P_COMP);
if (p->tag == P_PROCESSDEF) {
aip = fetchAllocationInfo(p);
} else {
assert(p->tag == P_COMP);
if (!doGenerateCode) {
aip = allocateAllocationInfo(p+1);
aip->isActivation = TRUE;
aip->scope = p;
aip->invokeQueueSize = sizeof(InvokeQueue);
} else {
aip = fetchAllocationInfo(p+1);
}
}
initializeTemplate("L_processTemplate", nextObjectNumber, FALSE);
generateTemplate(aip);
emit("L_processEP:\n");
lineNumberComment(p);
TS_startOperation(aip, nextObjectNumber, 10003);
if (p->tag == P_PROCESSDEF) {
assert(aip->parameterSize == 0);
doChildren(p);
} else {
generate(p->b.comp.consts);
}
TS_endOperation(FALSE, FALSE, FALSE);
}
void generateRecovery(p)
NodePtr p;
{
AllocationInfoPtr aip;
register NodePtr child;
if (p == NN) return;
assert(p->tag == P_RECOVERYDEF);
aip = fetchAllocationInfo(p);
initializeTemplate("L_recoveryTemplate", nextObjectNumber, TRUE);
generateTemplate(aip);
emit("L_recoveryEP:\n");
lineNumberComment(p);
TS_startOperation(aip, nextObjectNumber, 10002);
assert(aip->parameterSize == 0);
doChildren(p);
TS_endOperation(FALSE, FALSE, TRUE);
}
LoopRecordPtr loops = NULL;
extern void setHasInvokeQueueBit();
void generateTemplate(aip)
AllocationInfoPtr aip;
{
/*
* We know that the borings and locals do not have ab/cons, or else they
* would not be boring or local. The globals have ab/cons. The order,
* is monitor, borings, locals, globals in increasing offset order.
* For data areas this is increasing address order, and for activation records
* this is decreasing address order.
*/
int i, low1, high1, low2, high2, newi;
register NodePtr q;
register Symbol st;
nResultMoves = 0;
if (aip == NULL) return;
if (aip->isDataArea) {
assert(! aip->isActivation);
assert(aip->parameterSize == 0);
assert(aip->resultSize == 0);
assert(aip->invokeQueueSize == 0);
if (aip->monitorSize != 0) {
assert(aip->monitorSize == 8);
saveShortStaticTemplate(MonitorBrand, IsNotParam, DataBrand, 1, FALSE);
}
if (aip->boringSize > 0) {
assert(aip->boringSize % 4 == 0);
saveShortStaticTemplate(DataBrand, IsNotParam, DataBrand,
aip->boringSize, FALSE);
}
if (aip->localSize > 0) {
assert(aip->localSize % 4 == 0);
saveShortStaticTemplate(ODPBrand, IsNotParam, DataBrand,
aip->localSize / 4, FALSE);
}
if (aip->attachedLocalSize > 0) {
assert(aip->attachedLocalSize % 4 == 0);
saveShortStaticTemplate(ODPBrand, IsNotParam, DataBrand,
aip->attachedLocalSize / 4, TRUE);
}
if (aip->globalSize > 0) {
assert(aip->globalSize % 8 == 0);
saveShortStaticTemplate(VariableBrand, IsNotParam, DataBrand,
aip->globalSize / 8, FALSE);
}
if (aip->attachedGlobalSize > 0) {
assert(aip->attachedGlobalSize % 8 == 0);
saveShortStaticTemplate(VariableBrand, IsNotParam, DataBrand,
aip->attachedGlobalSize / 8, TRUE);
}
} else if (aip->isActivation) {
assert(! aip->isDataArea);
assert(aip->monitorSize == 0);
Sequence_For(q, aip->resultList)
st = q->b.symdef.symbol;
assert(st->itsKind == ST_Result);
if (st->isMove) nResultMoves++;
saveShortStaticTemplate(VariableBrand,
(ParamInfo)(st->isMove ? IsMoveResult : IsResult),
DataBrand, 1, st->isAttached);
Sequence_Next
Sequence_For(q, aip->paramList)
st = q->b.symdef.symbol;
assert(st->itsKind == ST_Param);
saveShortStaticTemplate(VariableBrand, IsArgument, DataBrand, 1,
st->isAttached);
Sequence_Next
if (aip->invokeQueueSize > 0) {
assert(aip->invokeQueueSize % sizeof(InvokeQueue) == 0);
saveShortStaticTemplate(InvokeQueueBrand, IsNotParam, DataBrand,
aip->invokeQueueSize / 8, FALSE);
setHasInvokeQueueBit(TRUE);
}
if (aip->boringSize > 0) {
assert(aip->boringSize % 4 == 0);
saveShortStaticTemplate(DataBrand, IsNotParam, DataBrand,
aip->boringSize, FALSE);
}
if (aip->localSize > 0) {
assert(aip->localSize % 4 == 0);
saveShortStaticTemplate(ODPBrand, IsNotParam, DataBrand,
aip->localSize / 4, FALSE);
}
if (aip->attachedLocalSize > 0) {
assert(aip->attachedLocalSize % 4 == 0);
saveShortStaticTemplate(ODPBrand, IsNotParam, DataBrand,
aip->attachedLocalSize / 4, TRUE);
}
if (aip->globalSize > 0) {
assert(aip->globalSize % 8 == 0);
saveShortStaticTemplate(VariableBrand, IsNotParam, DataBrand,
aip->globalSize / 8, FALSE);
}
if (aip->attachedGlobalSize > 0) {
assert(aip->attachedGlobalSize % 8 == 0);
saveShortStaticTemplate(VariableBrand, IsNotParam, DataBrand,
aip->attachedGlobalSize / 8, TRUE);
}
IFOPTION(allocateregisters, 1) {
low1 = low2 = high1 = high2 = -1;
for (i = 0; i < NALLOCATABLE; i++) {
newi = i;
if (aip->regs[i].isAllocated) {
switch (aip->regs[i].itsKind) {
case AK_Boring:
saveRegisterTemplate(DataBrand, InRegister, MINALLOCATABLE+i, 1,
FALSE);
break;
case AK_Local:
saveRegisterTemplate(ODPBrand, InRegister, MINALLOCATABLE+i, 1,
FALSE);
break;
case AK_AttachedLocal:
saveRegisterTemplate(ODPBrand, InRegister, MINALLOCATABLE+i, 1,
TRUE);
break;
case AK_Global:
saveRegisterTemplate(VariableBrand, InRegister, MINALLOCATABLE+i,
1, FALSE);
newi++;
break;
case AK_AttachedGlobal:
saveRegisterTemplate(VariableBrand, InRegister, MINALLOCATABLE+i,
1, TRUE);
newi++;
break;
default:
assert(FALSE);
break;
}
if (low1 == -1) {
low1 = i;
high1 = newi;
} else if (high1 == i-1) {
high1 = newi;
} else if (low2 == -1) {
low2 = i;
high2 = newi;
} else if (high2 == i-1) {
high2 = newi;
} else {
assert(FALSE);
}
i = newi;
}
}
if (low1 != -1) {
saveRegisterTemplate(DataBrand, InSaveArea, MINALLOCATABLE + low1,
high1 - low1 + 1, FALSE);
}
if (low2 != -1) {
saveRegisterTemplate(DataBrand, InSaveArea, MINALLOCATABLE + low2,
high2 - low2 + 1, FALSE);
}
#ifdef vax
assert(low2 == -1);
#endif
}
} else {
assert(FALSE);
}
}
extern Boolean easyGenerateObject();
extern char *writeAT();
void generateATObject(at)
NodePtr at;
{
/*
* This needs to build the code at like thingy, that has as its value
* some stuff so that we can perform type checking at run-time.
* Note that we also need to add to each Code at some stuff so that we
* can do type checking at run-time.
*/
register NodePtr p, q;
ODTag myTag;
int index;
Boolean hasNoPointer, immutable;
char *codeName, *ATInfo, *sourceFileName;
int codeNameLabel, ATInfoLabel, sourceFileNameLabel;
if (easyGenerateObject(at, at->b.atlit.id, 0)) {
nextObjectNumber++;
return;
}
emit(
" %c Copyright 1986 Eric Jul and Norm Hutchinson. May not be used\n",
COMMENTCHAR);
emit(
" %c for any purpose without written permission from the authors.\n",
COMMENTCHAR);
#ifdef vax
emit("\t.data\n");
#endif
#ifdef sun
emit("\t.text\n");
#endif
assert(at->b.atlit.name != NULL);
codeName = ST_SymbolName(at->b.atlit.name->b.symdef.symbol);
Comment("Abstract type named %s", codeName);
sourceFileName = at->tag == P_ATLIT && at->b.atlit.sfname ?
at->b.atlit.sfname->b.stringlit.string :
currentFileName;
Comment("Source file name %s", sourceFileName);
emit("L_beginCDA:\n");
inObject = TRUE;
immutable = at->b.atlit.f.immutable;
myTag = BuildTag(CodeTag, TRUE); /* codeTag */
if (at->b.atlit.id < (OID)0xff000100 && at->b.atlit.id > (OID)0xff000060) {
/*
* This is a builtin, and we need to be careful.
*/
index = at->b.atlit.id & 0x1f;
assert (index <= NUMBUILTINS);
switch (index) {
case BOOLEANINDEX:
case CHARACTERINDEX:
case INTEGERINDEX:
case NILINDEX:
case REALINDEX:
hasNoPointer = TRUE;
break;
default:
hasNoPointer = FALSE;
break;
}
myTag.allInstancesAreLocal = immutable | hasNoPointer;
myTag.hasNoPointer = hasNoPointer;
} else {
myTag.allInstancesAreLocal = immutable;
myTag.hasNoPointer = FALSE;
}
writeTag(myTag); /* codeTag */
writeHexComment(at->b.atlit.id, "Code OID"); /* OID */
currentCodeOID = at->b.atlit.id;
writeHex(OIDOfBuiltin(B_INSTAT, SIGNATUREINDEX));
writeHex((unsigned)EMVERSION);
/* code Name Offset */
emit("\t.long\tL_codeName - L_beginCDA\n");
emit("\t.long\tL_endCDA - L_beginCDA\n"); /* sizeOfThisCodeObject */
writeData(0); /* instanceSize */
#ifdef BADCC
writeTag(BuildTag(InvalidTag, immutable)); /* instanceTag */
#else
{
ODTag myTag;
myTag = BuildTag(InvalidTag, immutable);
writeTag(myTag);
}
#endif BADCC
writeData(0); /* ODATemplateOffset */
writeData(0); /* ipMapOffset */
writeData(0); /* failureHandlerMapOffset */
writeData(0); /* unavailableHandlerMapOffset */
writeData(0); /* lineNumberMapOffset */
if (Sequence_Length(at->b.atlit.ops) == 0) {
writeData(0);
} else {
emit("\t.long\tL_opVectorStart - L_beginCDA\n");
}
emit("\t.long\tL_relocInfoStart - L_beginCDA\n"); /* relocationInfoOffset */
emit("\t.long\tL_ATInfo - L_beginCDA\n"); /* at info offset */
writeData(0); /* initiallyEP */
writeData(0); /* initiallyTemplate */
writeWord(0);
writeWord(0);
writeHex(0);
writeData(0); /* recoveryEP */
writeData(0); /* recoveryTemplate */
writeWord(0);
writeWord(0);
writeHex(0);
writeData(0); /* processEP */
writeData(0); /* processTemplate */
writeWord(0);
writeWord(0);
writeHex(0);
emit("\t.long\tL_sourceFileName - L_beginCDA\n");
writeWord(0); /* ipMapOffset */
initializeRelocationInfo();
debugStart();
if (Sequence_Length(at->b.atlit.ops) != 0) {
emit("L_opVectorStart:\n");
writeData(Sequence_Length(at->b.atlit.ops));
Sequence_For(p, at->b.atlit.ops)
assert(p->tag == P_OPSIG);
q = p->b.opsig.name;
assert(q->tag == P_OPNAME);
writeData(0); /* entry point */
writeData(0); /* template offset */
writeWord(Sequence_Length(p->b.opsig.params));
writeWord(Sequence_Length(p->b.opsig.results));
writeHex(q->b.opname.id);
Sequence_Next
}
/* generate the AT info */
ATInfo = writeAT(at, FALSE, TRUE);
assert(ATInfo != NULL);
ATInfoLabel = nextLabelNumber++;
emitStringObject(ATInfo, ATInfoLabel, "ATInfo", nextObjectNumber);
/* generate the code name */
codeNameLabel = nextLabelNumber++;
emitStringObject(codeName, codeNameLabel, "codeName", nextObjectNumber);
/* generate the source file name */
sourceFileNameLabel = nextLabelNumber++;
emitStringObject(sourceFileName, sourceFileNameLabel, "sourceFileName",
nextObjectNumber);
debugDump();
dumpRelocationInfo();
emit("L_endCDA:\n");
writeData(0);
nextObjectNumber++;
}
void generateCodeObject(object, codeOID, monitorOps,
nonMonOps, initially, recovery, process, doCreate, createOID)
OID codeOID, createOID;
NodePtr object, monitorOps, nonMonOps, initially, recovery, process;
Boolean doCreate;
{
AllocationInfoPtr aip, initaip;
register int i;
register NodePtr ops, p, q;
int stage, index;
Boolean found, immutable, hasNoPointer, needsFunnyTemplate = FALSE;
ODTag myTag;
char *codeName, *sourceFileName;
int codeNameLabel, sourceFileNameLabel;
OID ownATOID;
OID debugVectorInstanceATOID;
int debugVectorSize;
if (easyGenerateObject(object, codeOID, doCreate ? createOID : 0)) {
nextObjectNumber++;
return;
}
currentObject = object;
nextOperationNumber = 0;
emit(
" %c Copyright 1986 Eric Jul and Norm Hutchinson. May not be used\n",
COMMENTCHAR);
emit(
" %c for any purpose without written permission from the authors.\n",
COMMENTCHAR);
#ifdef vax
emit("\t.data\n");
#endif
#ifdef sun
emit("\t.text\n");
#endif
codeName = object->tag == P_OBLIT ?
ST_SymbolName(object->b.oblit.name->b.symdef.symbol) :
"Compilation";
Comment("Code named %s", codeName);
sourceFileName = object->tag == P_OBLIT && object->b.oblit.sfname ?
object->b.oblit.sfname->b.stringlit.string :
currentFileName;
Comment("Source file name %s", sourceFileName);
ownATOID = object->tag == P_OBLIT ? getID(object->b.oblit.myat) : 0;
if (ownATOID != 0) ensureGenerate(ownATOID);
emit("L_beginCDA:\n");
inObject = TRUE;
aip = fetchAllocationInfo(object);
immutable = (object->tag == P_OBLIT && object->b.oblit.f.immutable);
myTag = BuildTag(CodeTag, TRUE); /* codeTag */
if (codeOID < (OID)0xff000100 && codeOID > (OID)0xff000060) {
/*
* This is a builtin, and we need to be careful.
*/
index = codeOID & 0x1f;
assert (index <= NUMBUILTINS);
switch (index) {
case BOOLEANINDEX:
case CHARACTERINDEX:
case INTEGERINDEX:
case NILINDEX:
case REALINDEX:
hasNoPointer = TRUE;
break;
case STRINGINDEX:
hasNoPointer = FALSE;
needsFunnyTemplate = TRUE;
break;
default:
hasNoPointer = FALSE;
break;
}
myTag.allInstancesAreLocal = immutable || hasNoPointer;
myTag.hasNoPointer = hasNoPointer;
} else {
myTag.allInstancesAreLocal = immutable;
myTag.hasNoPointer = FALSE;
}
IFTRACE(generate, 1) {
if (!doGenerateCode) {
printf("Generating code for object %s (0x%08x)\n", codeName, codeOID);
IFTRACE(generate, 3) {
if (object->tag == P_OBLIT) {
printf("\timmutable = %s\n", object->b.oblit.f.immutable ? "true" : "false");
printf("\tdoesNotDuplicateSelf = %s\n",
object->b.oblit.f.doesNotDuplicateSelf ? "true" : "false");
printf("\tdoesNotMoveArguments = %s\n",
object->b.oblit.f.doesNotMoveArguments ? "true" : "false");
printf("\tdoesNotMoveSelf = %s\n",
object->b.oblit.f.doesNotMoveSelf ? "true" : "false");
}
}
}
}
writeTag(myTag); /* myTag */
writeHexComment(codeOID, "Code OID"); /* OID */
currentCodeOID = codeOID;
writeHex(ownATOID); /* own AT OID */
writeHex((unsigned)EMVERSION);
/* code Name Offset */
emit("\t.long\tL_codeName - L_beginCDA\n");
emit("\t.long\tL_endCDA - L_beginCDA\n"); /* sizeOfThisCodeObject */
if (object->tag == P_OBLIT && object->b.oblit.f.isVector) {
/* the instance size of a vector is -1 */
writeData(-1);
} else if (object->tag == P_OBLIT && object->b.oblit.codeOID == OIDOfBuiltin(B_INSTCT, STRINGINDEX)) {
/* the instance size of a string is also -1 */
writeData(-1);
} else {
assert(aip->invokeQueueSize == 0);
writeData(firstInstanceOffset + aip->boringSize + aip->localSize +
aip->attachedLocalSize + aip->globalSize +
aip->attachedGlobalSize + aip->monitorSize +
(immutable ? sizeof(OID) : 0)); /* instanceSize */
}
#ifdef BADCC
writeTag(BuildTag(GODataTag, immutable)); /* instanceTag */
#else
{
ODTag myTag;
myTag = BuildTag(GODataTag, immutable);
writeTag(myTag);
}
#endif BADCC
emit("\t.long\tL_ODATemplate - L_beginCDA\n"); /* ODATemplateOffset */
emit("\t.long\tL_IPMapStart - L_beginCDA\n"); /* ipMapOffset */
if (doGenerateCode) {
if (mapHasEntries(failureHandlerMap)) {
emit("\t.long\tL_failureHandlerMap - L_beginCDA\n"); /* failureHandlerMapOffset */
} else {
writeData(0);
}
if (mapHasEntries(unavailableHandlerMap)) {
emit("\t.long\tL_unavailableHandlerMap - L_beginCDA\n"); /* unavailableHandlerMapOffset */
} else {
writeData(0);
}
if (mapHasEntries(lineNumberMap)) {
emit("\t.long\tL_lineNumberMap - L_beginCDA\n"); /* lineNumberMapOffset */
} else {
writeData(0);
}
}
if (monitorOps == NN && nonMonOps == NN) {
writeData(0);
} else {
emit("\t.long\tL_opVectorStart - L_beginCDA\n");
}
emit("\t.long\tL_relocInfoStart - L_beginCDA\n"); /* relocationInfoOffset */
writeHex(0); /* real code has no AT info */
if (initially != NN) {
emit("\t.long\tL_initiallyEP - L_beginCDA\n"); /* initiallyEP */
emit("\t.long\tL_initiallyTemplate - L_beginCDA\n");/* initiallyTemplate */
initaip = fetchAllocationInfo((NodePtr) ((int)initially + 1));
assert(initaip->parameterSize % 8 == 0);
assert(initaip->resultSize == 0);
writeWord(initaip->parameterSize / 8);
writeWord(0);
writeHex(0);
} else {
writeData(0); /* initiallyEP */
writeData(0); /* initiallyTemplate */
writeWord(0);
writeWord(0);
writeHex(0);
}
if (recovery != NN) {
emit("\t.long\tL_recoveryEP - L_beginCDA\n"); /* recoveryEP */
emit("\t.long\tL_recoveryTemplate - L_beginCDA\n"); /* recoveryTemplate */
writeWord(0);
writeWord(0);
writeHex(0);
} else {
writeData(0); /* recoveryEP */
writeData(0); /* recoveryTemplate */
writeWord(0);
writeWord(0);
writeHex(0);
}
if (process != NN) {
emit("\t.long\tL_processEP - L_beginCDA\n");/* processEP */
emit("\t.long\tL_processTemplate - L_beginCDA\n"); /* processTemplate */
writeWord(0);
writeWord(0);
writeHex(0);
} else {
writeData(0); /* processEP */
writeData(0); /* processTemplate */
writeWord(0);
writeWord(0);
writeHex(0);
}
emit("\t.long\tL_sourceFileName - L_beginCDA\n");
emit("\t.long\tL_debugInfoMap - L_beginCDA\n"); /* debugInfoMap*/
debugStart();
debugScope(1);
initializeRelocationInfo();
initializeTemplates();
initializeTemplate("L_ODATemplate", nextObjectNumber, FALSE);
if (object->tag == P_OBLIT && object->b.oblit.f.isVector) {
Symbol st;
Boolean isAttached = FALSE;
AllocateKind ak;
Brand instanceBrand;
aip->boringSize = 0;
aip->localSize = 0;
aip->attachedLocalSize = 0;
aip->globalSize = 0;
aip->attachedGlobalSize = 0;
aip->monitorSize = 0;
aip->conditionSize = 0;
if (object->b.oblit.codeOID == OIDOfBuiltin(B_INSTCT, BITCHUNKINDEX)) {
instanceBrand = DataBrand;
debugVectorSize = 4;
debugVectorInstanceATOID = OIDOfBuiltin(B_INSTAT, INTEGERINDEX);
} else {
st = getElementTypeSymbol(object);
isAttached = st->isAttached;
ATCTToSizeAndKind(st->value.ATinfo, st->value.CTinfo, st->isAttached,
&debugVectorSize, &ak);
assert(debugVectorSize != 0);
debugVectorInstanceATOID = OIDOf(st->value.ATinfo);
if (ak == AK_Global) instanceBrand = VariableBrand;
else if (ak == AK_Local) instanceBrand = ODPBrand;
else if (ak == AK_Boring) instanceBrand = DataBrand;
else assert(FALSE);
}
saveShortStaticTemplate(DataBrand, IsNotParam, DataBrand, 4, FALSE);
saveShortStaticTemplate(VectorBrand, IsNotParam, instanceBrand, 1,
isAttached);
} else if (needsFunnyTemplate) {
assert(index == STRINGINDEX);
saveShortStaticTemplate(VectorBrand, IsNotParam, DataBrand, 1, FALSE);
} else {
generateTemplate(aip);
}
/* start of the executable code */
emit("L_beginexecutable:\n");
initializeMaps();
/*
* We need to be careful about the children, because declarations need
* to be in the initially section even if there isnt one.
*/
if (monitorOps != NN || nonMonOps != NN) {
for (i = 0, found = TRUE; found; i++) {
found = FALSE;
for (stage = 0; stage < 2 && !found; stage++) {
if (stage == 0) {
ops = monitorOps;
} else if (stage == 1) {
ops = nonMonOps;
}
Sequence_For(p, ops)
assert(p->tag == P_OPDEF);
if (p->b.opdef.opNumber == i) {
inMonitor = (stage == 0 && !p->b.opdef.isPrivate);
generate(p);
found = TRUE;
break;
}
Sequence_Next
}
}
}
if (debugVectorSize) {
debugVector(debugVectorInstanceATOID, debugVectorSize);
debugVectorSize = 0;
}
if (initially != NN) generateInitially(initially);
if (process != NN) generateProcess(process);
if (recovery != NN) generateRecovery(recovery);
finalizeMaps();
debugScope(0);
emit("L_endexecutable:\n");
/* write the operation vector */
emit(ALIGNDIRECTIVE);
if (monitorOps != NN || nonMonOps != NN) {
emit("L_opVectorStart:\n");
writeData(nextOperationNumber);
for (i = 0; i < nextOperationNumber; i++) {
found = FALSE;
for (stage = 0; stage < 2 && !found; stage++) {
if (stage == 0) {
ops = monitorOps;
} else if (stage == 1) {
ops = nonMonOps;
}
Sequence_For(p, ops)
assert(p->tag == P_OPDEF);
if (p->b.opdef.opNumber == i) {
q = p->b.opdef.sig;
assert(q->tag == P_OPSIG);
p = q->b.opsig.name;
assert(p->tag == P_OPNAME);
emit("\t.long\tL_operationEP_%d - L_beginCDA\n", i);
emit(
"\t.long\tL_operationTemplate_%d - L_beginCDA\n", i);
writeWord(Sequence_Length(q->b.opsig.params));
writeWord(Sequence_Length(q->b.opsig.results));
writeHex(p->b.opname.id);
found = TRUE;
break;
}
Sequence_Next
}
assert(found);
}
}
/* generate the code name */
codeNameLabel = nextLabelNumber++;
emitStringObject(codeName, codeNameLabel, "codeName", nextObjectNumber);
/* generate the IP to template map */
emit("L_IPMapStart:\n");
#ifdef vax
emit("\t.long\tL_endexecutable - L_beginCDA - 1\n");
#endif
#ifdef sun
emit("\t.long\tL_endexecutable - L_beginCDA - 2\n");
#endif
emit("\t.long\tL_beginexecutable - L_beginCDA\n");
for (i = 0; i < nextOperationNumber; i++) {
emit("\t.long\tL_endoperation_%d - L_beginCDA\n", i);
emit("\t.long\tL_operationTemplate_%d - L_beginCDA\n", i);
}
if (initially != NN) {
emit("\t.long\tL_endoperation_%d - L_beginCDA\n", 10001);
emit("\t.long\tL_initiallyTemplate - L_beginCDA\n");
}
if (recovery != NN) {
emit("\t.long\tL_endoperation_%d - L_beginCDA\n", 10002);
emit("\t.long\tL_recoveryTemplate - L_beginCDA\n");
}
if (process != NN) {
emit("\t.long\tL_endoperation_%d - L_beginCDA\n", 10003);
emit("\t.long\tL_processTemplate - L_beginCDA\n");
}
/* generate the source file name */
sourceFileNameLabel = nextLabelNumber++;
emitStringObject(sourceFileName, sourceFileNameLabel, "sourceFileName",
nextObjectNumber);
/* generate the failureHandlerMap */
/* generate the unavailableHandlerMap */
/* generate the lineNumberMapOffset */
dumpMaps();
debugDump();
dumpStringLiterals();
dumpVectorLiterals();
dumpRelocationInfo();
dumpTemplates();
emit("L_endCDA:\n");
if (doCreate != 0) {
writeData(1);
writeHexComment(createOID, "\t\t\tCreate OID");
} else {
writeData(0);
}
currentObject = NN;
nextObjectNumber++;
}
extern NodePtr getCTInfo();
void generateResultAbCons(p)
register NodePtr p;
{
register NodePtr q;
register Symbol st;
DD varAbCon, valAbCon;
NodePtr ct;
Sequence_For(q, p)
assert(q->tag == P_PARAM);
q = q->b.param.sym;
assert(q->tag == P_SYMDEF);
st = ST_Fetch(q->b.symdef.symbol);
debugSymbol(st);
if ((ct = getCTInfo(st)) != NULL) {
varAbCon.kind = DD_Address;
varAbCon.value.address = st->v.address;
varAbCon = nextAddress(varAbCon);
valAbCon = buildAbCon(getID(st->value.ATinfo),getCodeID(ct));
emitMove(valAbCon, varAbCon, 'l');
}
Sequence_Next
}
fixDDView(source, target, oid, guaranteedWrong)
DD source, target;
OID oid;
Boolean guaranteedWrong;
{
NodePtr at;
DD kernelAbCon, variableAbOID, kernelAbOID, AbConAbOID;
at = OTLookup(oid);
assert(at->tag == P_ATLIT);
if (Sequence_Length(at->b.atlit.ops) == 0) {
/* we can use the existing at, since we won't do invokes */
if (! isSameDD(source, target)) {
emitMove(source, target, 'l');
}
return;
}
claimReg(regs_arg1, 1, ODPBrand);
kernelAbCon = buildRegisterDD(regs_arg1);
variableAbOID = buildManifestDD((int) oid);
IFOPTION(view, 1) {
claimReg(regs_arg2, 1, DataBrand);
} else IFOPTION(view, 2) {
claimReg(regs_arg2, 1, ODPBrand);
} else {
assert(FALSE);
}
kernelAbOID = buildRegisterDD(regs_arg2);
emitMove(source, kernelAbCon, 'l');
#ifdef sun
emit("\ttstl\t");
writeDD(kernelAbCon, '\n');
#endif
emit("\tj%s\t1f\n", JN(LSS));
if (!guaranteedWrong) {
AbConAbOID = increaseIndirection(kernelAbCon);
AbConAbOID.value.address.offset = AbCon_ATOID;
emit("\tcmpl\t");
writeDD(variableAbOID, ',');
writeDD(AbConAbOID, '\n');
emit("\tj%s\t1f\n", JN(EQL));
}
IFOPTION(view, 1) {
emitMove(variableAbOID, kernelAbOID, 'l');
preemptReg(regs_scratch, 1);
preemptReg(regs_arg3, 1);
generateKernelCall("em_changeview");
} else IFOPTION(view, 2) {
variableAbOID.kind = DD_OIDToCodePtr;
variableAbOID.value.id = oid;
emitMove(variableAbOID, kernelAbOID, 'l');
preemptReg(regs_scratch, 1);
preemptReg(regs_arg3, 1);
generateKernelCall("em_changeviewptr");
} else {
assert(FALSE);
}
freeDD(kernelAbOID);
if (guaranteedWrong) {
emitMove(kernelAbCon, target, 'l');
} else if (isSameDD(source, target)) {
emitMove(kernelAbCon, target, 'l');
emit("1:\n");
} else {
emit("1:\n");
emitMove(kernelAbCon, target, 'l');
}
freeDD(kernelAbCon);
ensureGenerate(oid);
}
void generateOneView(st)
register Symbol st;
{
DD variableAbCon;
if (getCTInfo(st) == NULL) {
variableAbCon.kind = DD_Address;
variableAbCon.value.address = st->v.address;
variableAbCon = nextAddress(variableAbCon);
fixDDView(variableAbCon, variableAbCon, getID(st->value.ATinfo), FALSE);
}
}
void generateArgumentViews(p)
register NodePtr p;
{
register NodePtr q;
register Symbol st;
Sequence_For(q, p)
assert(q->tag == P_PARAM);
q = q->b.param.sym;
assert(q->tag == P_SYMDEF);
st = ST_Fetch(q->b.symdef.symbol);
debugSymbol(st);
generateOneView(st);
Sequence_Next
}
void ensureGenerate(id)
OID id;
{
NodePtr p;
OC_Stage stage;
assert(id >= (OID)0xfe000000);
p = OTLookup(id);
assert((int)p != NIL);
assert(p->tag == P_OBLIT || p->tag == P_ATLIT);
if ((id & 0xffffff) <= (OID)0x000100) {
if (bflag) {
assert(thisBuiltin != NULL);
assert(thisBuiltin->tag == P_OBLIT);
if ((id & 0x1f) != (thisBuiltin->b.oblit.id & 0x1f)) {
TRACE2(builtins, 1, "Not generating code for %s with id 0x%08x", ATName(p),
id);
return;
}
} else {
return;
}
}
stage = (OC_Stage) Map_Lookup(ocMap, (int) p);
if ((int) stage == NIL) {
Map_Insert(ocMap, (int) p, (int) OC_Scheduled);
Sequence_Add(&ocStack, p);
return;
} else if (stage == OC_Done) {
return;
} else if (stage == OC_InProgress) {
return;
} else if (stage == OC_Scheduled) {
return;
} else assert(FALSE);
}
extern NodePtr theNode;
/* move exp to loc; fix exp at loc; unfix exp */
void generateLocationRequest(kernelCall, exp, loc)
char *kernelCall;
NodePtr exp, loc;
{
lineNumberComment(exp);
TS_StartInvocation();
if (exp != NN) {
vPush(pusherContext.v);
generateExpression(exp, pusherContext);
vGenerateAssign();
TS_Push();
}
if (loc != NN) {
generateExpression(loc, anyContext);
moveVariableToRegisters(vPeek(0), regs_arg1);
vDiscard();
}
preemptReg(regs_scratch, 1);
preemptReg(regs_arg3, 1);
TS_EndInvocation();
generateKernelCall(kernelCall);
}
extern void newAssignTypes(), typeCheck();
NodePtr findLiteral(p)
register NodePtr p;
{
NodePtr s, l;
assert(p->tag == P_IFCLAUSE);
p = p->b.ifclause.exp;
assert(p->tag == P_INVOC);
if (p->b.invoc.target->tag == P_SYMREF) {
s = p->b.invoc.target;
l = p->b.invoc.args->b.children[0]->b.arg.exp;
p->b.invoc.target = l;
p->b.invoc.args->b.children[0]->b.arg.exp = s;
}
p = p->b.invoc.target;
assert(p->tag == P_INTLIT || p->tag == P_CHARLIT);
return(p);
}
compareLiterals(pp, qp)
NodePtr *pp, *qp;
{
NodePtr p = findLiteral(*pp), q = findLiteral(*qp);
int l, r;
if (p->tag == P_INTLIT) {
l = atoi(p->b.intlit.string);
r = atoi(q->b.intlit.string);
} else {
l = (int) p->b.charlit.string[0];
r = (int) q->b.charlit.string[0];
}
return(l - r);
}
generateLabel(l, nl)
int l;
Boolean nl;
{
emit("L_%d:%s", l, nl ? "\n" : "");
}
generateCaseTable(p, s, nArms, minArm, maxArm, literalTag)
NodePtr p;
Symbol s;
int nArms, minArm, maxArm;
Tag literalTag;
{
int doneLabel, elseLabel, startLabel, nextLabel;
int thisArm, nextArm;
NodePtr r;
Variable arg2, arg3, extra;
DD symdd;
startLabel =nextLabelNumber++;
doneLabel = nextLabelNumber++;
elseLabel = p->b.ifstat.elseclause ? nextLabelNumber++ : doneLabel;
nextLabel = nextLabelNumber;
nextLabelNumber += nArms;
/*
* This sorts the if clauses, and has the side effect of cleaning up the
* individual invocations. Each is reordered so that the literal is the
* target of the invocation.
*/
qsort((char *)&(p->b.ifstat.ifclauses->b.children[0]),
Sequence_Length(p->b.ifstat.ifclauses),
sizeof(NodePtr),
compareLiterals);
/*
* Generate the preliminary stuff.
*/
symdd.kind = DD_Address;
symdd.value.address = s->v.address;
arg2.data = buildRegisterDDNC(regs_arg2);
arg2.abCon = buildConCon(INTEGERINDEX);
arg3.data = buildRegisterDDNC(regs_arg3);
arg3.abCon = arg2.abCon;
emitMove(symdd, arg2.data, 'l');
#ifdef sun
if (minArm != 0) {
emitMove(buildManifestDD(minArm), arg3.data, 'l');
emit("\tsubl\t"); writeDD(arg3.data, ','); writeDD(arg2.data, '\n');
}
emitMove(buildManifestDD(maxArm - minArm), arg3.data, 'l');
extra.data = generateCompare(&arg2, &arg3, 'l', GTRU);
extra.abCon = buildConCon(BOOLEANINDEX);
vPush(extra);
generateBranch(TRUE, elseLabel);
emit("\tmovw\tpc@(6,d0:l:2),d0\n");
emit("\tjmp\tpc@(2,d0:w)\n");
#endif
#ifdef vax
emit("\tcasel\t%s,$%d,$%d\n", RN(regs_arg2), minArm, maxArm-minArm);
#endif
generateLabel(startLabel, TRUE);
thisArm = minArm;
Sequence_For(r, p->b.ifstat.ifclauses)
switch (r->b.ifclause.exp->b.invoc.target->tag) {
case P_INTLIT:
nextArm = atoi(r->b.ifclause.exp->b.invoc.target->b.intlit.string);
break;
case P_CHARLIT:
nextArm = (int)r->b.ifclause.exp->b.invoc.target->b.charlit.string[0];
break;
}
if (nextArm < thisArm) continue;
for (; thisArm < nextArm; thisArm++) {
emit("\t.word\tL_%d-L_%d\n", elseLabel, startLabel);
}
emit("\t.word\tL_%d-L_%d\n", nextLabel + z__z, startLabel);
thisArm++;
Sequence_Next
if (p->b.ifstat.elseclause) {
generateLabel(elseLabel, TRUE);
lineNumberComment(p->b.ifstat.elseclause);
generate(p->b.ifstat.elseclause);
emit("\tj%s\tL_%d\n", JN(ALWAYS), doneLabel);
wroteCode = TRUE;
} else {
#ifdef vax
emit("\tj%s\tL_%d\n", JN(ALWAYS), doneLabel);
#endif
}
Sequence_For(r, p->b.ifstat.ifclauses)
generateLabel(nextLabel++, TRUE);
lineNumberComment(r->b.ifclause.stats);
generate(r->b.ifclause.stats);
if (z__z < Sequence_Length(p->b.ifstat.ifclauses) - 1) {
emit("\tj%s\tL_%d\n", JN(ALWAYS), doneLabel);
wroteCode = TRUE;
}
Sequence_Next
generateLabel(doneLabel, TRUE);
}
Boolean tryToUseCaseStatement(p)
register NodePtr p;
{
register NodePtr q, a1, a2, e, ct;
Symbol s = NULL;
static OID equalOID = 0;
Boolean result = TRUE;
Tag literalTag = T_NONE;
int nArms = 0, thisLabel, minLabel, maxLabel;
if (equalOID == 0) equalOID = ON_Translate("=");
assert(p->tag == P_IFSTAT);
Sequence_For(q, p->b.ifstat.ifclauses)
assert(q->tag == P_IFCLAUSE);
e = q->b.ifclause.exp;
if (e->tag != P_INVOC) { result = FALSE; break; }
if (e->b.invoc.opname->b.opname.id != equalOID) { result = FALSE; break; }
a1 = e->b.invoc.target;
if (Sequence_Length(e->b.invoc.args) != 1) { result = FALSE; break; }
a2 = e->b.invoc.args->b.children[0];
assert(a2->tag == P_ARG);
a2 = a2->b.arg.exp;
if (a1->tag != P_SYMREF) {
NodePtr t;
t = a1; a1 = a2; a2 = t;
}
if (a1->tag != P_SYMREF) { result = FALSE; break; }
if (a2->tag != P_INTLIT && a2->tag != P_CHARLIT) { result = FALSE; break; }
if (s != NULL && s != a1->b.symref.symbol) { result = FALSE; break; }
if (literalTag != T_NONE && literalTag != a2->tag) {result=FALSE;break;}
s = a1->b.symref.symbol;
literalTag = a2->tag;
nArms ++;
switch (literalTag) {
case P_INTLIT:
thisLabel = atoi(a2->b.intlit.string);
break;
case P_CHARLIT:
thisLabel = (int)a2->b.charlit.string[0];
break;
default:
assert(FALSE);
break;
}
if (nArms == 1 || thisLabel < minLabel) minLabel = thisLabel;
if (nArms == 1 || thisLabel > maxLabel) maxLabel = thisLabel;
Sequence_Next
if (result) {
ct = getCTInfo(s);
if (ct == NULL) {
result = FALSE;
} else if (ct->b.oblit.codeOID == OIDOfBuiltin(B_INSTCT, INTEGERINDEX)) {
if (literalTag != P_INTLIT) result = FALSE;
} else if (ct->b.oblit.codeOID == OIDOfBuiltin(B_INSTCT, CHARACTERINDEX)) {
if (literalTag != P_CHARLIT) result = FALSE;
}
if (nArms <= 2) result = FALSE;
/* we want to check the range */
if (nArms <= 10 && (double)(maxLabel - minLabel + 1) / nArms < 0.25) result = FALSE;
if ((maxLabel - minLabel + 1) > 512 &&
(double)(maxLabel - minLabel + 1) / nArms < 0.25) result = FALSE;
}
if (!result) return result;
generateCaseTable(p, s, nArms, minLabel, maxLabel, literalTag);
}
void generate(p)
register NodePtr p;
{
register NodePtr q, r, child;
register Symbol st;
OC_Stage stage;
int label1;
DD dd1, dd2;
register Variable *v;
AllocationInfoPtr aip;
char buffer[256];
static OID theCompilationOID;
int endLabel, falseLabel, tendLabel;
if ((int)p <= 0x200) return;
theNode = p;
switch (p->tag) {
case P_COMP:
doAllocate(p, doGenerateCode);
if (!doGenerateCode) theCompilationOID = AllocateOID();
generateCodeObject(p, theCompilationOID, NN, NN, NN, NN, p, TRUE, 0);
break;
case P_ATLIT:
stage = (OC_Stage) Map_Lookup(ocMap, (int) p);
if ((int) stage == NIL) {
assert(inObject);
Map_Insert(ocMap, (int) p, (int) OC_Scheduled);
Sequence_Add(&ocStack, p);
return;
} else if (stage == OC_Done) {
return;
} else if (stage == OC_InProgress) {
return;
} else if (stage == OC_Scheduled && inObject) {
return;
} else {
assert(stage == OC_Scheduled && ! inObject);
inObject = TRUE;
}
if (! p->b.atlit.f.isManifest) {
if (!doGenerateCode) nextObjectNumber++;
} else {
Map_Insert(ocMap, (int)p, OC_InProgress);
if (! bflag && !p->b.atlit.f.typesAreAssigned) {
TRACE1(delay, 1, "Need to assign types in %s", ATName(p));
newAssignTypes(p, 1);
}
if (!bflag && !p->b.atlit.f.typesHaveBeenChecked) {
TRACE1(delay, 1, "Need to type check %s", ATName(p));
typeCheck(p);
}
doAllocate(p, doGenerateCode);
generateATObject(p);
}
Map_Insert(ocMap, (int)p, OC_Done);
break;
case P_OBLIT:
stage = (OC_Stage) Map_Lookup(ocMap, (int) p);
if ((int) stage == NIL) {
assert(inObject);
Map_Insert(ocMap, (int) p, (int) OC_Scheduled);
Sequence_Add(&ocStack, p);
return;
} else if (stage == OC_Done) {
return;
} else if (stage == OC_InProgress) {
return;
} else if (stage == OC_Scheduled && inObject) {
return;
} else {
assert(stage == OC_Scheduled && ! inObject);
inObject = TRUE;
}
if (p->b.oblit.f.isTypeVariable || p->b.oblit.f.dependsOnTypeVariable) {
if (!doGenerateCode) nextObjectNumber++;
} else {
Map_Insert(ocMap, (int)p, OC_InProgress);
if (!bflag && !p->b.atlit.f.typesAreAssigned) {
TRACE1(delay, 1, "Need to assign types in %s", ATName(p));
newAssignTypes(p, 1);
}
if (!bflag && !p->b.atlit.f.typesHaveBeenChecked) {
TRACE1(delay, 1, "Need to type check %s", ATName(p));
typeCheck(p);
}
doAllocate(p, doGenerateCode);
generateCodeObject(p, getCodeOID(p),
p->b.oblit.monitor == NN ? NN : p->b.oblit.monitor->b.monitor.ops,
p->b.oblit.ops, hasInitially(p) ? p : NN,
p->b.oblit.monitor==NN ? NN :p->b.oblit.monitor->b.monitor.recovery,
p->b.oblit.process,
p->b.oblit.f.writeSeparately,
p->b.oblit.id);
}
Map_Insert(ocMap, (int)p, OC_Done);
break;
case P_SETQ:
st = ST_Fetch(p->b.setq.inner->b.symref.symbol);
if (isARealImport(st, TRUE)) {
if (st->usedOutsideInitially) {
Comment("Non-manifest setq of %s", ST_SymbolName(st));
debugSymbol(p->b.setq.inner->b.symdef.symbol);
generateAssign(p->b.setq.inner, p->b.setq.param);
generateOneView(st);
} else {
Comment("Non-manifest not used outside initially setq of %s",
ST_SymbolName(st));
st->v.address = p->b.setq.param->b.symdef.symbol->v.address;
generateOneView(ST_Fetch(p->b.setq.param->b.symdef.symbol));
}
} else {
Comment("Manifest setq of %s", ST_SymbolName(st));
}
break;
case P_VARDECL:
st = ST_Fetch(p->b.vardecl.sym->b.symdef.symbol);
if ((q = p->b.vardecl.value) != NN) {
lineNumberComment(p);
} else {
q = nilNode;
}
IFOPTION(comment, 1) Comment("Var Decl \"%s\" (addr %s)",
ST_SymbolName(st),addressToString(st->v.address));
debugSymbol(p->b.vardecl.sym->b.symdef.symbol);
generateAssign(p->b.vardecl.sym, q);
break;
case P_CONSTDECL:
st = ST_Fetch(p->b.constdecl.sym->b.symdef.symbol);
if (isAManifestConstant(st)) {
if (bflag && thisBuiltin == NULL) {
thisBuiltin = st->value.value;
TRACE1(builtins, 1, "This builtin is %s", ATName(thisBuiltin));
}
Comment("Manifest constant %s", ST_SymbolName(st));
ensureGenerate(getID(st->value.value));
} else {
lineNumberComment(p);
IFOPTION(comment, 1) Comment("Const Decl \"%s\" (addr %s)",
ST_SymbolName(st), addressToString(st->v.address));
debugSymbol(p->b.constdecl.sym->b.symdef.symbol);
generateAssign(p->b.constdecl.sym, p->b.constdecl.value);
}
break;
case P_WHEREWIDGIT:
if (p->b.wherewidgit.op == OCONFORMSTO) {
} else {
lineNumberComment(p);
st = ST_Fetch(p->b.wherewidgit.sym->b.symdef.symbol);
if (st->isManifest) {
generateAssign(p->b.wherewidgit.sym, st->value.value);
} else {
generateAssign(p->b.wherewidgit.sym, p->b.wherewidgit.type);
}
}
break;
case P_UNAVAILABLEHANDLER:
case P_FAILUREHANDLER:
break;
case P_BLOCK:
blockStart(p);
debugScope(1);
generate(p->b.block.stats);
debugScope(0);
blockEnd();
break;
case P_OPDEF:
aip = fetchAllocationInfo(p);
Comment("Operation Definition %s",
ON_Name(p->b.opdef.sig->b.opsig.name->b.opname.id));
debugScope(1);
sprintf(buffer, "L_operationTemplate_%d", p->b.opdef.opNumber);
initializeTemplate(buffer, 0, inMonitor);
generateTemplate(aip);
emit("L_operationEP_%d:\n", p->b.opdef.opNumber);
lineNumberComment(p);
wroteCode = TRUE;
TS_startOperation(aip, nextObjectNumber, p->b.opdef.opNumber);
if (gmflag && doGenerateCode) {
while (nResultMoves--) INC(cEM_callByResultMoves);
}
/* check for mustBeCompilerExecuted */
if (p->b.opdef.sig->b.opsig.mustBeCompilerExecuted) {
generateKernelCall("em_assertionFailure");
} else {
/* check on monitor entry */
if (inMonitor) {
assert(p->b.opdef.isMonitored);
generateMonEntry();
}
generateArgumentViews(p->b.opdef.sig->b.opsig.params);
generateResultAbCons(p->b.opdef.sig->b.opsig.results);
generate(p->b.opdef.body);
}
TS_endOperation(inMonitor, FALSE, FALSE);
debugScope(0);
nextOperationNumber ++;
freeAllRegs();
break;
case P_INITDEF:
debugScope(1);
generate(p->b.initdef.body);
debugScope(0);
break;
case P_OPSIG:
doChildren(p);
break;
case P_PRIMSTAT:
lineNumberComment(p);
generatePrimitive(p);
assert(vEmpty());
break;
case P_GLOBALREF:
resolveGlobal(p, (ValuePtr) NULL);
q = p->b.globalref.value;
generate(q);
break;
case P_INVOC:
assert(FALSE);
break;
case P_WAITSTAT:
lineNumberComment(p);
generateExpression(p->b.waitstat.exp, anyContext);
v = vPeek(0);
claimReg(regs_arg2, 1, ODPBrand);
dd1 = buildRegisterDD(regs_arg2);
emitMove(v->data, dd1, 'l');
vDiscard();
dd1.kind = DD_Address;
dd1.value.address = nullAddress;
dd1.value.address.base = Global;
dd1.value.address.offset = firstInstanceOffset;
if (currentObject->b.oblit.f.immutable)
dd1.value.address.offset += sizeof(OID);
claimReg(regs_arg1, 1, AddrBrand);
dd2 = buildRegisterDD(regs_arg1);
emitMoveAddress(dd1, dd2);
preemptReg(regs_scratch, 1);
preemptReg(regs_arg3, 1);
generateKernelCall("em_condWait");
freeReg(regs_arg1, 2);
assert(vEmpty());
break;
case P_SIGNALSTAT:
lineNumberComment(p);
generateExpression(p->b.signalstat.exp, anyContext);
v = vPeek(0);
claimReg(regs_arg2, 1, ODPBrand);
dd2 = buildRegisterDD(regs_arg2);
emitMove(v->data, dd2, 'l');
vDiscard();
dd1.kind = DD_Address;
dd1.value.address = nullAddress;
dd1.value.address.base = Global;
dd1.value.address.offset = firstInstanceOffset;
if (currentObject->b.oblit.f.immutable)
dd1.value.address.offset += sizeof(OID);
claimReg(regs_arg1, 1, AddrBrand);
dd2 = buildRegisterDD(regs_arg1);
emitMoveAddress(dd1, dd2);
preemptReg(regs_scratch, 1);
preemptReg(regs_arg3, 1);
if (p->b.signalstat.useSignalAndExit) {
generateKernelCall("em_condSignalAndExit");
emit("\tj%s\tL_operationreturnnomonexit_%d\n", JN(ALWAYS),
nextOperationNumber);
} else {
generateKernelCall("em_condSignal");
}
freeReg(regs_arg1, 2);
assert(vEmpty());
break;
case P_CHECKPOINTSTAT:
{
int flag = 0;
Variable v;
NodePtr loc = p->b.checkpointstat.loc;
lineNumberComment(p);
TS_StartInvocation();
if (p->b.checkpointstat.verb == (Token)T_NONE) {
flag = CHECKPOINT_DEFAULT;
} else if (p->b.checkpointstat.verb == KTO) {
flag = CHECKPOINT_TO;
} else if (p->b.checkpointstat.verb == KAT) {
if (p->b.checkpointstat.loc == (NodePtr) KALL) {
flag = CHECKPOINT_ATALL;
loc = NN;
} else {
flag = CHECKPOINT_AT;
}
} else {
assert(FALSE);
}
if (p->b.checkpointstat.confirm) flag = flag | CHECKPOINT_CONFIRM;
v.data = buildManifestDD(flag);
v.abCon = buildConCon(INTEGERINDEX);
moveDataToRegister(&v, regs_arg1, DataBrand);
if (loc == NN) loc = Construct(P_NILLIT, 0);
generateExpression(loc, anyContext);
moveVariableToRegisters(vPeek(0), regs_arg2);
vDiscard();
preemptReg(regs_scratch, 1);
freeReg(regs_arg1, 1);
TS_EndInvocation();
generateKernelCall("em_checkpoint");
}
break;
case P_RETURNSTAT:
lineNumberComment(p);
emit("\tj%s\tL_operationreturn_%d\n", JN(ALWAYS), opNumber);
break;
case P_RETURNANDFAILSTAT:
lineNumberComment(p);
if (inMonitor) generateMonExit();
generateKernelCall("em_returnAndFail");
break;
case P_LOOPSTAT:
debugScope(1);
{
LoopRecordPtr this = (LoopRecordPtr) malloc(sizeof(LoopRecord));
label1 = nextLabelNumber++;
this->label = nextLabelNumber++;
this->enclosing = loops;
loops = this;
emit("L_%d:\n", label1);
lineNumberComment(p);
doChildren(p);
#ifdef vax
emit("\tjlbc\t*$ _preemptFlag,L_%d\n", label1);
#endif
#ifdef sun
emit("\ttstl\t_preemptFlag\n");
emit("\tj%s\tL_%d\n", JN(EQL), label1);
#endif
generateKernelCall("em_loopPreempt");
emit("\tj%s\tL_%d\n", JN(ALWAYS), label1);
emit("L_%d:\n", this->label);
assert(loops == this);
loops = this->enclosing;
free((char *) this);
}
debugScope(0);
assert(vEmpty());
break;
case P_EXITSTAT:
lineNumberComment(p);
if (p->b.exitstat.exp != NULL) {
Variable *bool;
generateExpression(p->b.exitstat.exp, pslContext);
bool = vPeek(0);
vForceToTemp(bool, TS_Stack);
switch (bool->data.kind) {
case DD_Address:
emit("\ttstl\t");
writeDD(bool->data, '\n');
emit("\tj%s\tL_%d\n", JN(NEQ), loops->label);
break;
case DD_PSLCondition:
emit("\t%sj%s\tL_%d\n", JF(bool->data.value.condition.isFloat),
JN(bool->data.value.condition.psl), loops->label);
break;
case DD_Manifest:
if (bool->data.value.manifest) {
emit("\tj%s\tL_%d\n", JN(ALWAYS), loops->label);
} else {
/* no way to execute this code */
return;
}
break;
default:
assert(FALSE);
break;
}
vDiscard();
} else {
emit("\tj%s\tL_%d\n", JN(ALWAYS), loops->label);
}
assert(vEmpty());
break;
case P_ASSIGNSTAT:
lineNumberComment(p);
assert(p->b.assignstat.op == OASSIGN);
generateAssignStat(p);
assert(vEmpty());
break;
case P_ASSERTSTAT:
lineNumberComment(p);
{
Variable *bool;
label1 = nextLabelNumber++;
generateExpression(p->b.assertstat.exp, pslContext);
bool = vPeek(0);
vForceToTemp(bool, TS_Stack);
switch (bool->data.kind) {
case DD_Address:
emit("\ttstl\t%s\n", addressToString(bool->data.value.address));
emit("\tj%s\tL_%d\n", JN(NEQ), label1);
break;
case DD_PSLCondition:
emit("\t%sj%s\tL_%d\n", JF(bool->data.value.condition.isFloat),
JN(bool->data.value.condition.psl), label1);
break;
case DD_Manifest:
if (bool->data.value.manifest) {
/* assert true */
return;
} else {
/* assert false */
}
break;
default:
assert(FALSE);
break;
}
generateKernelCall("em_assertionFailure");
emit("L_%d:\n", label1);
wroteCode = TRUE;
vDiscard();
}
assert(vEmpty());
break;
case P_MOVESTAT:
INC(cEM_moves);
generateLocationRequest("em_move",p->b.movestat.exp, p->b.movestat.loc);
break;
case P_FIXSTAT:
INC(cEM_fixes);
generateLocationRequest("em_fix", p->b.fixstat.exp, p->b.fixstat.loc);
break;
case P_REFIXSTAT:
INC(cEM_refixes);
generateLocationRequest("em_refix", p->b.refixstat.exp, p->b.refixstat.loc);
break;
case P_UNFIXSTAT:
INC(cEM_unfixes);
generateLocationRequest("em_unfix", p->b.unfixstat.exp, NN);
break;
case P_IFSTAT:
lineNumberComment(p);
if (tryToUseCaseStatement(p)) break;
endLabel = nextLabelNumber++;
q = p->b.ifstat.ifclauses;
Sequence_For(r, q)
falseLabel = nextLabelNumber++;
if (p->b.ifstat.elseclause == NN && z__z == q->nChildren-1) {
tendLabel = 0;
} else {
tendLabel = endLabel;
}
generateIfClause(r, tendLabel, falseLabel);
emit("L_%d:\n", falseLabel);
Sequence_Next
if (p->b.ifstat.elseclause != NULL) {
lineNumberComment(p->b.ifstat.elseclause);
debugScope(1);
generate(p->b.ifstat.elseclause);
debugScope(0);
}
emit("L_%d:\n", endLabel);
assert(vEmpty());
break;
case P_IFCLAUSE:
assert(FALSE);
break;
case P_ELSECLAUSE:
generate(p->b.elseclause.stats);
assert(vEmpty());
break;
case T_SEQUENCE:
doChildren(p);
break;
default:
emit("%s\n", tagNames[(int)p->tag]);
doChildren(p);
break;
}
}
void generatePrimitive(p)
register NodePtr p;
{
register NodePtr primno;
int nargs, i;
Variable vTarget, *target = &vTarget;
Boolean hasResult = FALSE;
Symbol st;
Context resultContext;
assert(p->tag == P_PRIMSTAT);
target->data = buildRegisterDD(regs_g);
target->abCon = buildAbConFromObject(currentObject);
primno = p->b.primstat.number;
if (Sequence_Length(p->b.primstat.vars) > 0) {
assert(Sequence_Length(p->b.primstat.vars) == 1);
st = ST_Fetch(p->b.primstat.vars->b.children[0]->b.symref.symbol);
vPushVariable(st);
hasResult = TRUE;
resultContext.kind = C_Variable;
resultContext.v = vTop();
} else {
resultContext = anyContext;
}
nargs = Sequence_Length(p->b.primstat.vals);
for (i = 0; i < nargs; i++) {
generateExpression(p->b.primstat.vals->b.children[i], anyContext);
}
/*
* DoPrimitive leaves the result (if there is one) on the variable stack.
*/
doPrimitive(currentObject, p, primno, target, nargs, hasResult,
resultContext);
if (hasResult) {
vGenerateAssign();
}
}
generateOneGuy(p)
NodePtr p;
{
doGenerateCode = FALSE;
nextLabelNumber = 101;
generate(p);
Map_Insert(ocMap, (int)p, OC_Scheduled);
nextObjectNumber --;
nextLabelNumber = 101;
inObject = FALSE;
doGenerateCode = TRUE;
generate(p);
}
void generateCode(p)
NodePtr p;
{
NodePtr q;
assert(p->tag == P_COMP);
inObject = TRUE;
generateOneGuy(p);
while (Sequence_Length(ocStack) > 0) {
q = ocStack->b.children[ocStack->nChildren-1];
ocStack->nChildren--;
inObject = FALSE;
generateOneGuy(q);
}
printStatistics();
}
printStatistics()
{
if (!gmflag) return;
TRACE1(passes, 1, "totalInvokes = %4d", cEM_totalInvokes);
TRACE1(passes, 1, "directInvokes = %4d", cEM_directInvokes);
TRACE1(passes, 1, "inlinedInvokes = %4d", cEM_inlinedInvokes);
TRACE1(passes, 1, "localInvokes = %4d", cEM_localInvokes);
TRACE1(passes, 1, "selfInvokes = %4d", cEM_selfInvokes);
TRACE1(passes, 1, "KCTimmutableInvokes = %4d", cEM_KCTimmutableInvokes);
TRACE1(passes, 1, "UKCTimmutableInvokes = %4d", cEM_UKCTimmutableInvokes);
TRACE1(passes, 1, "KCTresidentGlobalInvokes = %4d",
cEM_KCTresidentGlobalInvokes);
TRACE1(passes, 1, "UKCTresidentGlobalInvokes = %4d",
cEM_UKCTresidentGlobalInvokes);
TRACE1(passes, 1, "moves = %4d", cEM_moves);
TRACE1(passes, 1, "fixes = %4d", cEM_fixes);
TRACE1(passes, 1, "unfixes = %4d", cEM_unfixes);
TRACE1(passes, 1, "refixes = %4d", cEM_refixes);
TRACE1(passes, 1, "locates = %4d", cEM_locates);
TRACE1(passes, 1, "callByMoves = %4d", cEM_callByMoves);
TRACE1(passes, 1, "callByVisits = %4d", cEM_callByVisits);
TRACE1(passes, 1, "callByResultMoves = %4d", cEM_callByResultMoves);
}